module Hix.Options where
import Exon (exon)
import Options.Applicative (
CommandFields,
Mod,
Parser,
ReadM,
auto,
bashCompleter,
command,
completer,
customExecParser,
fullDesc,
header,
help,
helper,
hsubparser,
info,
long,
metavar,
option,
prefs,
progDesc,
short,
showDefault,
showHelpOnEmpty,
showHelpOnError,
strArgument,
strOption,
subparserInline,
switch,
value,
)
import Path (Abs, Dir, File, Path, SomeBase, parseRelDir, parseSomeDir)
import Path.IO (getCurrentDir)
import Prelude hiding (Mod, mod)
import qualified Hix.Data.BootstrapProjectConfig
import Hix.Data.BootstrapProjectConfig (BootstrapProjectConfig (BootstrapProjectConfig))
import Hix.Data.ComponentConfig (ComponentName (ComponentName), ModuleName, SourceDir (SourceDir))
import Hix.Data.EnvName (EnvName)
import Hix.Data.GhciConfig (ChangeDir (ChangeDir), RunnerName)
import Hix.Data.GlobalOptions (GlobalOptions (..))
import qualified Hix.Data.NewProjectConfig
import Hix.Data.NewProjectConfig (NewProjectConfig (NewProjectConfig))
import qualified Hix.Data.Options
import Hix.Data.Options (
BootstrapOptions (..),
BumpOptions (..),
Command (..),
ComponentCoords (ComponentCoords),
ComponentSpec (..),
EnvRunnerCommandOptions (..),
EnvRunnerOptions (EnvRunnerOptions, component, config, root),
ExtraGhciOptions,
ExtraGhcidOptions,
GhciOptions (..),
GhcidOptions (..),
LowerCommand (..),
LowerOptions (LowerOptions),
ManagedOptions (ManagedOptions),
NewOptions (..),
Options (Options),
PackageSpec (..),
PreprocOptions (PreprocOptions),
ProjectOptions (ProjectOptions),
TargetSpec (..),
TestOptions (..),
)
import Hix.Data.OutputFormat (OutputFormat (OutputNone))
import Hix.Data.OutputTarget (OutputTarget (OutputDefault))
import Hix.Data.PackageName (PackageName (PackageName))
import qualified Hix.Managed.Cabal.Data.Config
import Hix.Managed.Cabal.Data.Config (CabalConfig (CabalConfig))
import qualified Hix.Managed.Data.BuildConfig
import Hix.Managed.Data.BuildConfig (BuildConfig (BuildConfig))
import Hix.Managed.Data.Query (RawQuery (RawQuery))
import qualified Hix.Managed.Data.StateFileConfig
import Hix.Managed.Data.StateFileConfig (StateFileConfig (StateFileConfig))
import Hix.Managed.Handlers.Build (BuildTimeout (BuildTimeout))
import Hix.Optparse (
JsonConfig,
absDirOption,
absFileOption,
absFileOrCwdOption,
buildHandlersOption,
indexStateOption,
jsonOption,
outputFormatOption,
outputTargetOption,
relFileOption,
someFileOption,
)
fileParser ::
ReadM a ->
String ->
String ->
Parser a
fileParser :: forall a. ReadM a -> String -> String -> Parser a
fileParser ReadM a
readOption String
longName String
helpText =
ReadM a -> Mod OptionFields a -> Parser a
forall a. ReadM a -> Mod OptionFields a -> Parser a
option ReadM a
readOption (String -> Mod OptionFields a
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
longName Mod OptionFields a -> Mod OptionFields a -> Mod OptionFields a
forall a. Semigroup a => a -> a -> a
<> Completer -> Mod OptionFields a
forall (f :: * -> *) a. HasCompleter f => Completer -> Mod f a
completer (String -> Completer
bashCompleter String
"file") Mod OptionFields a -> Mod OptionFields a -> Mod OptionFields a
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields a
forall (f :: * -> *) a. String -> Mod f a
help String
helpText)
absFileParser :: String -> String -> Parser (Path Abs File)
absFileParser :: String -> String -> Parser (Path Abs File)
absFileParser = ReadM (Path Abs File) -> String -> String -> Parser (Path Abs File)
forall a. ReadM a -> String -> String -> Parser a
fileParser ReadM (Path Abs File)
absFileOption
absFileOrCwdParser :: Path Abs Dir -> String -> String -> Parser (Path Abs File)
absFileOrCwdParser :: Path Abs Dir -> String -> String -> Parser (Path Abs File)
absFileOrCwdParser Path Abs Dir
cwd = ReadM (Path Abs File) -> String -> String -> Parser (Path Abs File)
forall a. ReadM a -> String -> String -> Parser a
fileParser (Path Abs Dir -> ReadM (Path Abs File)
absFileOrCwdOption Path Abs Dir
cwd)
someFileParser :: String -> String -> Parser (SomeBase File)
someFileParser :: String -> String -> Parser (SomeBase File)
someFileParser = ReadM (SomeBase File) -> String -> String -> Parser (SomeBase File)
forall a. ReadM a -> String -> String -> Parser a
fileParser ReadM (SomeBase File)
someFileOption
rootParser :: Parser (Maybe (Path Abs Dir))
rootParser :: Parser (Maybe (Path Abs Dir))
rootParser =
Parser (Path Abs Dir) -> Parser (Maybe (Path Abs Dir))
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (ReadM (Path Abs Dir)
-> Mod OptionFields (Path Abs Dir) -> Parser (Path Abs Dir)
forall a. ReadM a -> Mod OptionFields a -> Parser a
option ReadM (Path Abs Dir)
absDirOption (String -> Mod OptionFields (Path Abs Dir)
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"root" Mod OptionFields (Path Abs Dir)
-> Mod OptionFields (Path Abs Dir)
-> Mod OptionFields (Path Abs Dir)
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields (Path Abs Dir)
forall (f :: * -> *) a. String -> Mod f a
help String
"The root directory of the project"))
jsonConfigParser ::
Parser JsonConfig
jsonConfigParser :: Parser JsonConfig
jsonConfigParser =
ReadM JsonConfig
-> Mod OptionFields JsonConfig -> Parser JsonConfig
forall a. ReadM a -> Mod OptionFields a -> Parser a
option ReadM JsonConfig
jsonOption (String -> Mod OptionFields JsonConfig
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"config" Mod OptionFields JsonConfig
-> Mod OptionFields JsonConfig -> Mod OptionFields JsonConfig
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields JsonConfig
forall (f :: * -> *) a. String -> Mod f a
help String
"The Hix-generated config, file or text")
preprocParser ::
Path Abs Dir ->
Parser PreprocOptions
preprocParser :: Path Abs Dir -> Parser PreprocOptions
preprocParser Path Abs Dir
cwd =
Maybe (Either PreprocConfig JsonConfig)
-> Maybe (Path Abs Dir)
-> Path Abs File
-> Path Abs File
-> Path Abs File
-> PreprocOptions
PreprocOptions
(Maybe (Either PreprocConfig JsonConfig)
-> Maybe (Path Abs Dir)
-> Path Abs File
-> Path Abs File
-> Path Abs File
-> PreprocOptions)
-> Parser (Maybe (Either PreprocConfig JsonConfig))
-> Parser
(Maybe (Path Abs Dir)
-> Path Abs File
-> Path Abs File
-> Path Abs File
-> PreprocOptions)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
((JsonConfig -> Either PreprocConfig JsonConfig)
-> Maybe JsonConfig -> Maybe (Either PreprocConfig JsonConfig)
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JsonConfig -> Either PreprocConfig JsonConfig
forall a b. b -> Either a b
Right (Maybe JsonConfig -> Maybe (Either PreprocConfig JsonConfig))
-> Parser (Maybe JsonConfig)
-> Parser (Maybe (Either PreprocConfig JsonConfig))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser JsonConfig -> Parser (Maybe JsonConfig)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional Parser JsonConfig
jsonConfigParser)
Parser
(Maybe (Path Abs Dir)
-> Path Abs File
-> Path Abs File
-> Path Abs File
-> PreprocOptions)
-> Parser (Maybe (Path Abs Dir))
-> Parser
(Path Abs File -> Path Abs File -> Path Abs File -> PreprocOptions)
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 (Path Abs Dir))
rootParser
Parser
(Path Abs File -> Path Abs File -> Path Abs File -> PreprocOptions)
-> Parser (Path Abs File)
-> Parser (Path Abs File -> Path Abs File -> PreprocOptions)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
Path Abs Dir -> String -> String -> Parser (Path Abs File)
absFileOrCwdParser Path Abs Dir
cwd String
"source" String
"The original source file"
Parser (Path Abs File -> Path Abs File -> PreprocOptions)
-> Parser (Path Abs File)
-> Parser (Path Abs File -> PreprocOptions)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
Path Abs Dir -> String -> String -> Parser (Path Abs File)
absFileOrCwdParser Path Abs Dir
cwd String
"in" String
"The prepared input file"
Parser (Path Abs File -> PreprocOptions)
-> Parser (Path Abs File) -> Parser PreprocOptions
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
Path Abs Dir -> String -> String -> Parser (Path Abs File)
absFileOrCwdParser Path Abs Dir
cwd String
"out" String
"The path to the output file"
packageSpecParser :: Parser (Maybe PackageSpec)
packageSpecParser :: Parser (Maybe PackageSpec)
packageSpecParser = do
Parser Text -> Parser (Maybe Text)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (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
"package" Mod OptionFields Text
-> Mod OptionFields Text -> Mod OptionFields Text
forall a. Semigroup a => a -> a -> a
<> Char -> Mod OptionFields Text
forall (f :: * -> *) a. HasName f => Char -> Mod f a
short Char
'p' 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
"The name or directory of the test package")) Parser (Maybe Text)
-> (Maybe Text -> Maybe PackageSpec) -> Parser (Maybe PackageSpec)
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> (Text -> PackageSpec) -> Maybe Text -> Maybe PackageSpec
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap \ Text
name ->
PackageSpec {name :: PackageName
name = Text -> PackageName
PackageName Text
name, dir :: Maybe (SomeBase Dir)
dir = String -> Maybe (SomeBase Dir)
forall (m :: * -> *). MonadThrow m => String -> m (SomeBase Dir)
parseSomeDir (Text -> String
forall a. ToString a => a -> String
toString Text
name)}
componentSpecParser :: Parser (Maybe ComponentSpec)
componentSpecParser :: Parser (Maybe ComponentSpec)
componentSpecParser = do
Parser Text -> Parser (Maybe Text)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (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
"component" Mod OptionFields Text
-> Mod OptionFields Text -> Mod OptionFields Text
forall a. Semigroup a => a -> a -> a
<> Char -> Mod OptionFields Text
forall (f :: * -> *) a. HasName f => Char -> Mod f a
short Char
'c' 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
h)) Parser (Maybe Text)
-> (Maybe Text -> Maybe ComponentSpec)
-> Parser (Maybe ComponentSpec)
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> (Text -> ComponentSpec) -> Maybe Text -> Maybe ComponentSpec
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap \ Text
name ->
ComponentSpec {name :: ComponentName
name = Text -> ComponentName
ComponentName Text
name, dir :: Maybe SourceDir
dir = Path Rel Dir -> SourceDir
SourceDir (Path Rel Dir -> SourceDir)
-> Maybe (Path Rel Dir) -> Maybe SourceDir
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> Maybe (Path Rel Dir)
forall (m :: * -> *). MonadThrow m => String -> m (Path Rel Dir)
parseRelDir (Text -> String
forall a. ToString a => a -> String
toString Text
name)}
where
h :: String
h = String
"The name or relative directory of the test component"
componentCoordsParser :: Parser ComponentCoords
componentCoordsParser :: Parser ComponentCoords
componentCoordsParser =
Maybe PackageSpec -> Maybe ComponentSpec -> ComponentCoords
ComponentCoords
(Maybe PackageSpec -> Maybe ComponentSpec -> ComponentCoords)
-> Parser (Maybe PackageSpec)
-> Parser (Maybe ComponentSpec -> ComponentCoords)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
Parser (Maybe PackageSpec)
packageSpecParser
Parser (Maybe ComponentSpec -> ComponentCoords)
-> Parser (Maybe ComponentSpec) -> Parser ComponentCoords
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 ComponentSpec)
componentSpecParser
componentForFileParser ::
Path Abs Dir ->
Parser TargetSpec
componentForFileParser :: Path Abs Dir -> Parser TargetSpec
componentForFileParser Path Abs Dir
cwd =
Path Abs File -> TargetSpec
TargetForFile
(Path Abs File -> TargetSpec)
-> Parser (Path Abs File) -> Parser TargetSpec
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
ReadM (Path Abs File)
-> Mod OptionFields (Path Abs File) -> Parser (Path Abs File)
forall a. ReadM a -> Mod OptionFields a -> Parser a
option (Path Abs Dir -> ReadM (Path Abs File)
absFileOrCwdOption Path Abs Dir
cwd) (String -> Mod OptionFields (Path Abs File)
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"file" Mod OptionFields (Path Abs File)
-> Mod OptionFields (Path Abs File)
-> Mod OptionFields (Path Abs File)
forall a. Semigroup a => a -> a -> a
<> Char -> Mod OptionFields (Path Abs File)
forall (f :: * -> *) a. HasName f => Char -> Mod f a
short Char
'f' Mod OptionFields (Path Abs File)
-> Mod OptionFields (Path Abs File)
-> Mod OptionFields (Path Abs File)
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields (Path Abs File)
forall (f :: * -> *) a. String -> Mod f a
help String
"The absolute file path of the test module")
targetSpecParser ::
Path Abs Dir ->
Parser TargetSpec
targetSpecParser :: Path Abs Dir -> Parser TargetSpec
targetSpecParser Path Abs Dir
cwd =
Path Abs Dir -> Parser TargetSpec
componentForFileParser Path Abs Dir
cwd
Parser TargetSpec -> Parser TargetSpec -> Parser TargetSpec
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
ComponentCoords -> TargetSpec
TargetForComponent (ComponentCoords -> TargetSpec)
-> Parser ComponentCoords -> Parser TargetSpec
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser ComponentCoords
componentCoordsParser
envNameParser :: Parser EnvName
envNameParser :: Parser EnvName
envNameParser =
Mod OptionFields EnvName -> Parser EnvName
forall s. IsString s => Mod OptionFields s -> Parser s
strOption (String -> Mod OptionFields EnvName
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"env" Mod OptionFields EnvName
-> Mod OptionFields EnvName -> Mod OptionFields EnvName
forall a. Semigroup a => a -> a -> a
<> Char -> Mod OptionFields EnvName
forall (f :: * -> *) a. HasName f => Char -> Mod f a
short Char
'e' Mod OptionFields EnvName
-> Mod OptionFields EnvName -> Mod OptionFields EnvName
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields EnvName
forall (f :: * -> *) a. String -> Mod f a
help String
"The name of the environment")
testParser :: Parser (Maybe Text)
testParser :: Parser (Maybe Text)
testParser =
Parser Text -> Parser (Maybe Text)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (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
"test" Mod OptionFields Text
-> Mod OptionFields Text -> Mod OptionFields Text
forall a. Semigroup a => a -> a -> a
<> Char -> Mod OptionFields Text
forall (f :: * -> *) a. HasName f => Char -> Mod f a
short Char
't' 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
"The Haskell function that should be executed"))
runnerParser :: Parser (Maybe RunnerName)
runnerParser :: Parser (Maybe RunnerName)
runnerParser =
Parser RunnerName -> Parser (Maybe RunnerName)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (Mod OptionFields RunnerName -> Parser RunnerName
forall s. IsString s => Mod OptionFields s -> Parser s
strOption (
String -> Mod OptionFields RunnerName
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"run"
Mod OptionFields RunnerName
-> Mod OptionFields RunnerName -> Mod OptionFields RunnerName
forall a. Semigroup a => a -> a -> a
<>
Char -> Mod OptionFields RunnerName
forall (f :: * -> *) a. HasName f => Char -> Mod f a
short Char
'r'
Mod OptionFields RunnerName
-> Mod OptionFields RunnerName -> Mod OptionFields RunnerName
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields RunnerName
forall (f :: * -> *) a. String -> Mod f a
help String
"The name of the command defined in the Hix option 'ghci.run'"
))
cdParser :: Parser ChangeDir
cdParser :: Parser ChangeDir
cdParser =
Bool -> ChangeDir
ChangeDir (Bool -> ChangeDir) -> (Bool -> Bool) -> Bool -> ChangeDir
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Bool
not (Bool -> ChangeDir) -> Parser Bool -> Parser ChangeDir
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Mod FlagFields Bool -> Parser Bool
switch (String -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"no-cd" 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
"Don't change the working directory to the package root")
moduleParser :: Parser ModuleName
moduleParser :: Parser ModuleName
moduleParser =
Mod OptionFields ModuleName -> Parser ModuleName
forall s. IsString s => Mod OptionFields s -> Parser s
strOption (String -> Mod OptionFields ModuleName
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"module" Mod OptionFields ModuleName
-> Mod OptionFields ModuleName -> Mod OptionFields ModuleName
forall a. Semigroup a => a -> a -> a
<> Char -> Mod OptionFields ModuleName
forall (f :: * -> *) a. HasName f => Char -> Mod f a
short Char
'm' Mod OptionFields ModuleName
-> Mod OptionFields ModuleName -> Mod OptionFields ModuleName
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields ModuleName
forall (f :: * -> *) a. String -> Mod f a
help String
"The module containing the test function" Mod OptionFields ModuleName
-> Mod OptionFields ModuleName -> Mod OptionFields ModuleName
forall a. Semigroup a => a -> a -> a
<> ModuleName -> Mod OptionFields ModuleName
forall (f :: * -> *) a. HasValue f => a -> Mod f a
value ModuleName
"Main")
testOptionsParser :: Parser TestOptions
testOptionsParser :: Parser TestOptions
testOptionsParser = do
Maybe Text
test <- Parser (Maybe Text)
testParser
Maybe RunnerName
runner <- Parser (Maybe RunnerName)
runnerParser
ModuleName
mod <- Parser ModuleName
moduleParser
ChangeDir
cd <- Parser ChangeDir
cdParser
pure TestOptions {Maybe Text
Maybe RunnerName
ModuleName
ChangeDir
test :: Maybe Text
runner :: Maybe RunnerName
mod :: ModuleName
cd :: ChangeDir
cd :: ChangeDir
runner :: Maybe RunnerName
test :: Maybe Text
mod :: ModuleName
..}
extraGhciParser :: Parser (Maybe ExtraGhciOptions)
=
Parser ExtraGhciOptions -> Parser (Maybe ExtraGhciOptions)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (Mod OptionFields ExtraGhciOptions -> Parser ExtraGhciOptions
forall s. IsString s => Mod OptionFields s -> Parser s
strOption (String -> Mod OptionFields ExtraGhciOptions
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"ghci-options" Mod OptionFields ExtraGhciOptions
-> Mod OptionFields ExtraGhciOptions
-> Mod OptionFields ExtraGhciOptions
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields ExtraGhciOptions
forall (f :: * -> *) a. String -> Mod f a
help String
"Additional command line options to pass to ghci"))
extraGhcidParser :: Parser (Maybe ExtraGhcidOptions)
=
Parser ExtraGhcidOptions -> Parser (Maybe ExtraGhcidOptions)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (Mod OptionFields ExtraGhcidOptions -> Parser ExtraGhcidOptions
forall s. IsString s => Mod OptionFields s -> Parser s
strOption (String -> Mod OptionFields ExtraGhcidOptions
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"ghcid-options" Mod OptionFields ExtraGhcidOptions
-> Mod OptionFields ExtraGhcidOptions
-> Mod OptionFields ExtraGhcidOptions
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields ExtraGhcidOptions
forall (f :: * -> *) a. String -> Mod f a
help String
"Additional command line options to pass to ghcid"))
envParser ::
Path Abs Dir ->
Parser EnvRunnerCommandOptions
envParser :: Path Abs Dir -> Parser EnvRunnerCommandOptions
envParser Path Abs Dir
cwd = do
EnvRunnerOptions
options <- do
Either EnvConfig JsonConfig
config <- JsonConfig -> Either EnvConfig JsonConfig
forall a b. b -> Either a b
Right (JsonConfig -> Either EnvConfig JsonConfig)
-> Parser JsonConfig -> Parser (Either EnvConfig JsonConfig)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser JsonConfig
jsonConfigParser
Maybe (Path Abs Dir)
root <- Parser (Maybe (Path Abs Dir))
rootParser
Maybe TargetSpec
component <- Parser TargetSpec -> Parser (Maybe TargetSpec)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (Path Abs Dir -> Parser TargetSpec
targetSpecParser Path Abs Dir
cwd)
pure EnvRunnerOptions {Maybe (Path Abs Dir)
Maybe TargetSpec
Either EnvConfig JsonConfig
component :: Maybe TargetSpec
config :: Either EnvConfig JsonConfig
root :: Maybe (Path Abs Dir)
config :: Either EnvConfig JsonConfig
root :: Maybe (Path Abs Dir)
component :: Maybe TargetSpec
..}
TestOptions
test <- Parser TestOptions
testOptionsParser
Maybe ExtraGhciOptions
extraGhci <- Parser (Maybe ExtraGhciOptions)
extraGhciParser
Maybe ExtraGhcidOptions
extraGhcid <- Parser (Maybe ExtraGhcidOptions)
extraGhcidParser
pure EnvRunnerCommandOptions {Maybe ExtraGhcidOptions
Maybe ExtraGhciOptions
EnvRunnerOptions
TestOptions
options :: EnvRunnerOptions
test :: TestOptions
extraGhci :: Maybe ExtraGhciOptions
extraGhcid :: Maybe ExtraGhcidOptions
extraGhcid :: Maybe ExtraGhcidOptions
extraGhci :: Maybe ExtraGhciOptions
test :: TestOptions
options :: EnvRunnerOptions
..}
ghciParser ::
Path Abs Dir ->
Parser GhciOptions
ghciParser :: Path Abs Dir -> Parser GhciOptions
ghciParser Path Abs Dir
cwd = do
Either GhciConfig JsonConfig
config <- JsonConfig -> Either GhciConfig JsonConfig
forall a b. b -> Either a b
Right (JsonConfig -> Either GhciConfig JsonConfig)
-> Parser JsonConfig -> Parser (Either GhciConfig JsonConfig)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser JsonConfig
jsonConfigParser
Maybe (Path Abs Dir)
root <- Parser (Maybe (Path Abs Dir))
rootParser
TargetSpec
component <- Path Abs Dir -> Parser TargetSpec
targetSpecParser Path Abs Dir
cwd
TestOptions
test <- Parser TestOptions
testOptionsParser
Maybe ExtraGhciOptions
extra <- Parser (Maybe ExtraGhciOptions)
extraGhciParser
pure GhciOptions {Maybe (Path Abs Dir)
Maybe ExtraGhciOptions
Either GhciConfig JsonConfig
TestOptions
TargetSpec
config :: Either GhciConfig JsonConfig
root :: Maybe (Path Abs Dir)
component :: TargetSpec
test :: TestOptions
extra :: Maybe ExtraGhciOptions
extra :: Maybe ExtraGhciOptions
test :: TestOptions
component :: TargetSpec
root :: Maybe (Path Abs Dir)
config :: Either GhciConfig JsonConfig
..}
ghcidParser ::
Path Abs Dir ->
Parser GhcidOptions
ghcidParser :: Path Abs Dir -> Parser GhcidOptions
ghcidParser Path Abs Dir
cwd = do
GhciOptions
ghci <- Path Abs Dir -> Parser GhciOptions
ghciParser Path Abs Dir
cwd
Maybe ExtraGhcidOptions
extra <- Parser (Maybe ExtraGhcidOptions)
extraGhcidParser
pure GhcidOptions {Maybe ExtraGhcidOptions
GhciOptions
ghci :: GhciOptions
extra :: Maybe ExtraGhcidOptions
extra :: Maybe ExtraGhcidOptions
ghci :: GhciOptions
..}
newParser :: Parser NewOptions
newParser :: Parser NewOptions
newParser = do
ProjectName
name <- Mod OptionFields ProjectName -> Parser ProjectName
forall s. IsString s => Mod OptionFields s -> Parser s
strOption (String -> Mod OptionFields ProjectName
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"name" Mod OptionFields ProjectName
-> Mod OptionFields ProjectName -> Mod OptionFields ProjectName
forall a. Semigroup a => a -> a -> a
<> Char -> Mod OptionFields ProjectName
forall (f :: * -> *) a. HasName f => Char -> Mod f a
short Char
'n' Mod OptionFields ProjectName
-> Mod OptionFields ProjectName -> Mod OptionFields ProjectName
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields ProjectName
forall (f :: * -> *) a. String -> Mod f a
help String
"The name of the new project and its main package")
Bool
packages <- Mod FlagFields Bool -> Parser Bool
switch (String -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"packages" Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<> Char -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => Char -> Mod f a
short Char
'p' 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
"Store packages in the 'packages/' subdirectory")
HixUrl
hixUrl <- Mod OptionFields HixUrl -> Parser HixUrl
forall s. IsString s => Mod OptionFields s -> Parser s
strOption (String -> Mod OptionFields HixUrl
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"hix-url" Mod OptionFields HixUrl
-> Mod OptionFields HixUrl -> Mod OptionFields HixUrl
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields HixUrl
forall (f :: * -> *) a. String -> Mod f a
help String
"The URL to the Hix repository" Mod OptionFields HixUrl
-> Mod OptionFields HixUrl -> Mod OptionFields HixUrl
forall a. Semigroup a => a -> a -> a
<> HixUrl -> Mod OptionFields HixUrl
forall (f :: * -> *) a. HasValue f => a -> Mod f a
value HixUrl
forall a. Default a => a
def)
Author
author <- Mod OptionFields Author -> Parser Author
forall s. IsString s => Mod OptionFields s -> Parser s
strOption (String -> Mod OptionFields Author
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"author" Mod OptionFields Author
-> Mod OptionFields Author -> Mod OptionFields Author
forall a. Semigroup a => a -> a -> a
<> Char -> Mod OptionFields Author
forall (f :: * -> *) a. HasName f => Char -> Mod f a
short Char
'a' Mod OptionFields Author
-> Mod OptionFields Author -> Mod OptionFields Author
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields Author
forall (f :: * -> *) a. String -> Mod f a
help String
"Your name" Mod OptionFields Author
-> Mod OptionFields Author -> Mod OptionFields Author
forall a. Semigroup a => a -> a -> a
<> Author -> Mod OptionFields Author
forall (f :: * -> *) a. HasValue f => a -> Mod f a
value Author
"Author")
pure NewOptions {config :: NewProjectConfig
config = NewProjectConfig {Bool
Author
HixUrl
ProjectName
name :: ProjectName
packages :: Bool
hixUrl :: HixUrl
author :: Author
author :: Author
hixUrl :: HixUrl
packages :: Bool
name :: ProjectName
..}}
bootstrapParser :: Parser BootstrapOptions
bootstrapParser :: Parser BootstrapOptions
bootstrapParser = do
HixUrl
hixUrl <- Mod OptionFields HixUrl -> Parser HixUrl
forall s. IsString s => Mod OptionFields s -> Parser s
strOption (String -> Mod OptionFields HixUrl
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"hix-url" Mod OptionFields HixUrl
-> Mod OptionFields HixUrl -> Mod OptionFields HixUrl
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields HixUrl
forall (f :: * -> *) a. String -> Mod f a
help String
"The URL to the Hix repository" Mod OptionFields HixUrl
-> Mod OptionFields HixUrl -> Mod OptionFields HixUrl
forall a. Semigroup a => a -> a -> a
<> HixUrl -> Mod OptionFields HixUrl
forall (f :: * -> *) a. HasValue f => a -> Mod f a
value HixUrl
forall a. Default a => a
def)
pure BootstrapOptions {config :: BootstrapProjectConfig
config = BootstrapProjectConfig {HixUrl
hixUrl :: HixUrl
hixUrl :: HixUrl
..}}
stateFileConfigParser :: Parser StateFileConfig
stateFileConfigParser :: Parser StateFileConfig
stateFileConfigParser = do
Path Rel File
file <- ReadM (Path Rel File)
-> Mod OptionFields (Path Rel File) -> Parser (Path Rel File)
forall a. ReadM a -> Mod OptionFields a -> Parser a
option ReadM (Path Rel File)
relFileOption (String -> Mod OptionFields (Path Rel File)
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"file" Mod OptionFields (Path Rel File)
-> Mod OptionFields (Path Rel File)
-> Mod OptionFields (Path Rel File)
forall a. Semigroup a => a -> a -> a
<> Char -> Mod OptionFields (Path Rel File)
forall (f :: * -> *) a. HasName f => Char -> Mod f a
short Char
'f' Mod OptionFields (Path Rel File)
-> Mod OptionFields (Path Rel File)
-> Mod OptionFields (Path Rel File)
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields (Path Rel File)
forall (f :: * -> *) a. String -> Mod f a
help String
"The relative path to the managed deps file")
Maybe (Path Abs Dir)
projectRoot <- Parser (Path Abs Dir) -> Parser (Maybe (Path Abs Dir))
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (ReadM (Path Abs Dir)
-> Mod OptionFields (Path Abs Dir) -> Parser (Path Abs Dir)
forall a. ReadM a -> Mod OptionFields a -> Parser a
option ReadM (Path Abs Dir)
absDirOption (String -> Mod OptionFields (Path Abs Dir)
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"root" Mod OptionFields (Path Abs Dir)
-> Mod OptionFields (Path Abs Dir)
-> Mod OptionFields (Path Abs Dir)
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields (Path Abs Dir)
forall (f :: * -> *) a. String -> Mod f a
help String
"The root directory of the project"))
pure StateFileConfig {Maybe (Path Abs Dir)
Path Rel File
file :: Path Rel File
projectRoot :: Maybe (Path Abs Dir)
projectRoot :: Maybe (Path Abs Dir)
file :: Path Rel File
..}
cabalConfigParser :: Parser CabalConfig
cabalConfigParser :: Parser CabalConfig
cabalConfigParser = do
Maybe HackageIndexState
indexState <- Parser HackageIndexState -> Parser (Maybe HackageIndexState)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (ReadM HackageIndexState
-> Mod OptionFields HackageIndexState -> Parser HackageIndexState
forall a. ReadM a -> Mod OptionFields a -> Parser a
option ReadM HackageIndexState
indexStateOption (String -> Mod OptionFields HackageIndexState
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"index-state" Mod OptionFields HackageIndexState
-> Mod OptionFields HackageIndexState
-> Mod OptionFields HackageIndexState
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields HackageIndexState
forall (f :: * -> *) a. String -> Mod f a
help String
indexStateHelp))
pure CabalConfig {Maybe HackageIndexState
indexState :: Maybe HackageIndexState
indexState :: Maybe HackageIndexState
..}
where
indexStateHelp :: String
indexStateHelp = String
"The index state for Hackage, Unix stamp or date string"
buildConfigParser :: Parser BuildConfig
buildConfigParser :: Parser BuildConfig
buildConfigParser = do
Natural
maxIterations <- ReadM Natural -> Mod OptionFields Natural -> Parser Natural
forall a. ReadM a -> Mod OptionFields a -> Parser a
option ReadM Natural
forall a. Read a => ReadM a
auto (String -> Mod OptionFields Natural
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"max-iterations" Mod OptionFields Natural
-> Mod OptionFields Natural -> Mod OptionFields Natural
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields Natural
forall (f :: * -> *) a. String -> Mod f a
help String
maxIterationsHelp Mod OptionFields Natural
-> Mod OptionFields Natural -> Mod OptionFields Natural
forall a. Semigroup a => a -> a -> a
<> Natural -> Mod OptionFields Natural
forall (f :: * -> *) a. HasValue f => a -> Mod f a
value Natural
3 Mod OptionFields Natural
-> Mod OptionFields Natural -> Mod OptionFields Natural
forall a. Semigroup a => a -> a -> a
<> Mod OptionFields Natural
forall a (f :: * -> *). Show a => Mod f a
showDefault)
Natural
maxFailedPre <- ReadM Natural -> Mod OptionFields Natural -> Parser Natural
forall a. ReadM a -> Mod OptionFields a -> Parser a
option ReadM Natural
forall a. Read a => ReadM a
auto (String -> Mod OptionFields Natural
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"max-failed-majors-pre" Mod OptionFields Natural
-> Mod OptionFields Natural -> Mod OptionFields Natural
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields Natural
forall (f :: * -> *) a. String -> Mod f a
help String
maxFailedPreHelp Mod OptionFields Natural
-> Mod OptionFields Natural -> Mod OptionFields Natural
forall a. Semigroup a => a -> a -> a
<> Natural -> Mod OptionFields Natural
forall (f :: * -> *) a. HasValue f => a -> Mod f a
value Natural
99 Mod OptionFields Natural
-> Mod OptionFields Natural -> Mod OptionFields Natural
forall a. Semigroup a => a -> a -> a
<> Mod OptionFields Natural
forall a (f :: * -> *). Show a => Mod f a
showDefault)
Natural
maxFailedPost <- ReadM Natural -> Mod OptionFields Natural -> Parser Natural
forall a. ReadM a -> Mod OptionFields a -> Parser a
option ReadM Natural
forall a. Read a => ReadM a
auto (String -> Mod OptionFields Natural
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"max-failed-majors-post" Mod OptionFields Natural
-> Mod OptionFields Natural -> Mod OptionFields Natural
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields Natural
forall (f :: * -> *) a. String -> Mod f a
help String
maxFailedPostHelp Mod OptionFields Natural
-> Mod OptionFields Natural -> Mod OptionFields Natural
forall a. Semigroup a => a -> a -> a
<> Natural -> Mod OptionFields Natural
forall (f :: * -> *) a. HasValue f => a -> Mod f a
value Natural
0 Mod OptionFields Natural
-> Mod OptionFields Natural -> Mod OptionFields Natural
forall a. Semigroup a => a -> a -> a
<> Mod OptionFields Natural
forall a (f :: * -> *). Show a => Mod f a
showDefault)
Bool
lookup <- Mod FlagFields Bool -> Parser Bool
switch (String -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"lookup" Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<> Char -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => Char -> Mod f a
short Char
'n' 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
"Only print latest versions (bump)")
Bool
validate <- Mod FlagFields Bool -> Parser Bool
switch (String -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"validate" 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
"Validate new versions, but don't update the project state")
Bool
buildOutput <- Mod FlagFields Bool -> Parser Bool
switch (String -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"build-output" 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
"Show output from Nix builds")
Maybe BuildTimeout
timeout <- (Int -> BuildTimeout) -> Maybe Int -> Maybe BuildTimeout
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Int -> BuildTimeout
BuildTimeout (Maybe Int -> Maybe BuildTimeout)
-> Parser (Maybe Int) -> Parser (Maybe BuildTimeout)
forall (f :: * -> *) a b. Functor 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
"build-timeout" 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
buildTimeoutHelp))
Bool
disableNixMonitor <- Mod FlagFields Bool -> Parser Bool
switch (String -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"disable-nix-monitor" 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
"Don't parse Nix build output")
pure BuildConfig {Bool
Natural
Maybe BuildTimeout
maxIterations :: Natural
maxFailedPre :: Natural
maxFailedPost :: Natural
lookup :: Bool
validate :: Bool
buildOutput :: Bool
timeout :: Maybe BuildTimeout
disableNixMonitor :: Bool
toposortMutations :: Bool
disableNixMonitor :: Bool
timeout :: Maybe BuildTimeout
toposortMutations :: Bool
buildOutput :: Bool
validate :: Bool
lookup :: Bool
maxFailedPost :: Natural
maxFailedPre :: Natural
maxIterations :: Natural
..}
where
maxIterationsHelp :: String
maxIterationsHelp = String
"Number of restarts when some dependencies fail"
maxFailedPreHelp :: String
maxFailedPreHelp = String -> String
forall {inner} {builder}.
(ExonAppend inner builder, ExonString inner builder,
ExonBuilder inner builder) =>
inner -> inner
maxFailedHelp String
"prior to the first"
maxFailedPostHelp :: String
maxFailedPostHelp = String -> String
forall {inner} {builder}.
(ExonAppend inner builder, ExonString inner builder,
ExonBuilder inner builder) =>
inner -> inner
maxFailedHelp String
"after the last"
maxFailedHelp :: inner -> inner
maxFailedHelp inner
variant = [exon|Number of majors that may fail before aborting, #{variant} success|]
buildTimeoutHelp :: String
buildTimeoutHelp = String
"Kill Nix builds after this duration in seconds"
toposortMutations :: Bool
toposortMutations = Bool
True
projectOptionsParser :: Parser ProjectOptions
projectOptionsParser :: Parser ProjectOptions
projectOptionsParser = do
BuildConfig
build <- Parser BuildConfig
buildConfigParser
RawQuery
query <- [PackageName] -> RawQuery
RawQuery ([PackageName] -> RawQuery)
-> Parser [PackageName] -> Parser RawQuery
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser PackageName -> Parser [PackageName]
forall a. Parser a -> Parser [a]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
many (Mod ArgumentFields PackageName -> Parser PackageName
forall s. IsString s => Mod ArgumentFields s -> Parser s
strArgument (String -> Mod ArgumentFields PackageName
forall (f :: * -> *) a. String -> Mod f a
help String
"Positional arguments select individual deps for processing"))
[EnvName]
envs <- Parser EnvName -> Parser [EnvName]
forall a. Parser a -> Parser [a]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
some (Mod OptionFields EnvName -> Parser EnvName
forall s. IsString s => Mod OptionFields s -> Parser s
strOption (String -> Mod OptionFields EnvName
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"env" Mod OptionFields EnvName
-> Mod OptionFields EnvName -> Mod OptionFields EnvName
forall a. Semigroup a => a -> a -> a
<> Char -> Mod OptionFields EnvName
forall (f :: * -> *) a. HasName f => Char -> Mod f a
short Char
'e' Mod OptionFields EnvName
-> Mod OptionFields EnvName -> Mod OptionFields EnvName
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields EnvName
forall (f :: * -> *) a. String -> Mod f a
help String
"Environments whose packages should be updated"))
Bool
readUpperBounds <- Mod FlagFields Bool -> Parser Bool
switch (String -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"read-upper-bounds" 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
"Use the upper bounds from the flake for the first run")
Bool
mergeBounds <- Mod FlagFields Bool -> Parser Bool
switch (String -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"merge-bounds" 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
"Always add the flake bounds to the managed bounds")
pure ProjectOptions {Bool
[EnvName]
RawQuery
BuildConfig
build :: BuildConfig
query :: RawQuery
envs :: [EnvName]
readUpperBounds :: Bool
mergeBounds :: Bool
mergeBounds :: Bool
readUpperBounds :: Bool
query :: RawQuery
envs :: [EnvName]
build :: BuildConfig
..}
managedOptionsParser :: Parser ManagedOptions
managedOptionsParser :: Parser ManagedOptions
managedOptionsParser = do
Either ProjectContextProto JsonConfig
context <- JsonConfig -> Either ProjectContextProto JsonConfig
forall a b. b -> Either a b
Right (JsonConfig -> Either ProjectContextProto JsonConfig)
-> Parser JsonConfig
-> Parser (Either ProjectContextProto JsonConfig)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser JsonConfig
jsonConfigParser
ProjectOptions
project <- Parser ProjectOptions
projectOptionsParser
StateFileConfig
stateFile <- Parser StateFileConfig
stateFileConfigParser
Maybe SpecialBuildHandlers
handlers <- Parser SpecialBuildHandlers -> Parser (Maybe SpecialBuildHandlers)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (ReadM SpecialBuildHandlers
-> Mod OptionFields SpecialBuildHandlers
-> Parser SpecialBuildHandlers
forall a. ReadM a -> Mod OptionFields a -> Parser a
option ReadM SpecialBuildHandlers
buildHandlersOption (String -> Mod OptionFields SpecialBuildHandlers
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"handlers" Mod OptionFields SpecialBuildHandlers
-> Mod OptionFields SpecialBuildHandlers
-> Mod OptionFields SpecialBuildHandlers
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields SpecialBuildHandlers
forall (f :: * -> *) a. String -> Mod f a
help String
"Internal: Handlers for tests"))
CabalConfig
cabal <- Parser CabalConfig
cabalConfigParser
pure ManagedOptions {Maybe SpecialBuildHandlers
Either ProjectContextProto JsonConfig
StateFileConfig
CabalConfig
ProjectOptions
context :: Either ProjectContextProto JsonConfig
project :: ProjectOptions
stateFile :: StateFileConfig
handlers :: Maybe SpecialBuildHandlers
cabal :: CabalConfig
handlers :: Maybe SpecialBuildHandlers
cabal :: CabalConfig
stateFile :: StateFileConfig
project :: ProjectOptions
context :: Either ProjectContextProto JsonConfig
..}
bumpParser :: Parser BumpOptions
bumpParser :: Parser BumpOptions
bumpParser = do
ManagedOptions
common <- Parser ManagedOptions
managedOptionsParser
pure BumpOptions {ManagedOptions
common :: ManagedOptions
common :: ManagedOptions
..}
lowerParser :: Parser LowerOptions
lowerParser :: Parser LowerOptions
lowerParser = do
Bool
initOnly <- Mod FlagFields Bool -> Parser Bool
switch (String -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"init" 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
"Only initialize missing lower bounds")
Bool
reset <- Mod FlagFields Bool -> Parser Bool
switch (String -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"reset" 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
"Reinitialize bounds of all deps rather than just new ones")
Bool
stabilize <- Mod FlagFields Bool -> Parser Bool
switch (String -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"stabilize" 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
"Attempt to find working bounds if the current ones are broken")
ManagedOptions
common <- Parser ManagedOptions
managedOptionsParser
pure LowerOptions {Bool
ManagedOptions
initOnly :: Bool
reset :: Bool
stabilize :: Bool
common :: ManagedOptions
stabilize :: Bool
reset :: Bool
initOnly :: Bool
common :: ManagedOptions
..}
lowerCommands :: Mod CommandFields LowerCommand
lowerCommands :: Mod CommandFields LowerCommand
lowerCommands =
String -> ParserInfo LowerCommand -> Mod CommandFields LowerCommand
forall a. String -> ParserInfo a -> Mod CommandFields a
command String
"init" (LowerOptions -> LowerCommand
LowerInitCmd (LowerOptions -> LowerCommand)
-> ParserInfo LowerOptions -> ParserInfo LowerCommand
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser LowerOptions
-> InfoMod LowerOptions -> ParserInfo LowerOptions
forall a. Parser a -> InfoMod a -> ParserInfo a
info Parser LowerOptions
lowerParser (String -> InfoMod LowerOptions
forall a. String -> InfoMod a
progDesc String
"Initialize the lower bounds"))
Mod CommandFields LowerCommand
-> Mod CommandFields LowerCommand -> Mod CommandFields LowerCommand
forall a. Semigroup a => a -> a -> a
<>
String -> ParserInfo LowerCommand -> Mod CommandFields LowerCommand
forall a. String -> ParserInfo a -> Mod CommandFields a
command String
"optimize" (LowerOptions -> LowerCommand
LowerOptimizeCmd (LowerOptions -> LowerCommand)
-> ParserInfo LowerOptions -> ParserInfo LowerCommand
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser LowerOptions
-> InfoMod LowerOptions -> ParserInfo LowerOptions
forall a. Parser a -> InfoMod a -> ParserInfo a
info Parser LowerOptions
lowerParser (String -> InfoMod LowerOptions
forall a. String -> InfoMod a
progDesc String
"Optimize the lower bounds"))
Mod CommandFields LowerCommand
-> Mod CommandFields LowerCommand -> Mod CommandFields LowerCommand
forall a. Semigroup a => a -> a -> a
<>
String -> ParserInfo LowerCommand -> Mod CommandFields LowerCommand
forall a. String -> ParserInfo a -> Mod CommandFields a
command String
"stabilize" (LowerOptions -> LowerCommand
LowerStabilizeCmd (LowerOptions -> LowerCommand)
-> ParserInfo LowerOptions -> ParserInfo LowerCommand
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser LowerOptions
-> InfoMod LowerOptions -> ParserInfo LowerOptions
forall a. Parser a -> InfoMod a -> ParserInfo a
info Parser LowerOptions
lowerParser (String -> InfoMod LowerOptions
forall a. String -> InfoMod a
progDesc String
"Stabilize the lower bounds"))
Mod CommandFields LowerCommand
-> Mod CommandFields LowerCommand -> Mod CommandFields LowerCommand
forall a. Semigroup a => a -> a -> a
<>
String -> ParserInfo LowerCommand -> Mod CommandFields LowerCommand
forall a. String -> ParserInfo a -> Mod CommandFields a
command String
"auto" (LowerOptions -> LowerCommand
LowerAutoCmd (LowerOptions -> LowerCommand)
-> ParserInfo LowerOptions -> ParserInfo LowerCommand
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser LowerOptions
-> InfoMod LowerOptions -> ParserInfo LowerOptions
forall a. Parser a -> InfoMod a -> ParserInfo a
info Parser LowerOptions
lowerParser (String -> InfoMod LowerOptions
forall a. String -> InfoMod a
progDesc String
"Process the lower bounds"))
lowerCommand :: Parser LowerCommand
lowerCommand :: Parser LowerCommand
lowerCommand =
Mod CommandFields LowerCommand -> Parser LowerCommand
forall a. Mod CommandFields a -> Parser a
hsubparser Mod CommandFields LowerCommand
lowerCommands Parser LowerCommand -> Parser LowerCommand -> Parser LowerCommand
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (LowerOptions -> LowerCommand
LowerAutoCmd (LowerOptions -> LowerCommand)
-> Parser LowerOptions -> Parser LowerCommand
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser LowerOptions
lowerParser)
managedCommitMsgParser :: Parser (Path Abs File)
managedCommitMsgParser :: Parser (Path Abs File)
managedCommitMsgParser =
ReadM (Path Abs File)
-> Mod OptionFields (Path Abs File) -> Parser (Path Abs File)
forall a. ReadM a -> Mod OptionFields a -> Parser a
option ReadM (Path Abs File)
absFileOption (String -> Mod OptionFields (Path Abs File)
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"file" Mod OptionFields (Path Abs File)
-> Mod OptionFields (Path Abs File)
-> Mod OptionFields (Path Abs File)
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields (Path Abs File)
forall (f :: * -> *) a. String -> Mod f a
help String
"The JSON file written by a managed deps app")
managedGithubPrParser :: Parser (Path Abs File)
managedGithubPrParser :: Parser (Path Abs File)
managedGithubPrParser =
ReadM (Path Abs File)
-> Mod OptionFields (Path Abs File) -> Parser (Path Abs File)
forall a. ReadM a -> Mod OptionFields a -> Parser a
option ReadM (Path Abs File)
absFileOption (String -> Mod OptionFields (Path Abs File)
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"file" Mod OptionFields (Path Abs File)
-> Mod OptionFields (Path Abs File)
-> Mod OptionFields (Path Abs File)
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields (Path Abs File)
forall (f :: * -> *) a. String -> Mod f a
help String
"The JSON file written by a managed deps app")
commands ::
Path Abs Dir ->
Mod CommandFields Command
commands :: Path Abs Dir -> Mod CommandFields Command
commands Path Abs Dir
cwd =
String -> ParserInfo Command -> Mod CommandFields Command
forall a. String -> ParserInfo a -> Mod CommandFields a
command String
"preproc" (PreprocOptions -> Command
Preproc (PreprocOptions -> Command)
-> ParserInfo PreprocOptions -> ParserInfo Command
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser PreprocOptions
-> InfoMod PreprocOptions -> ParserInfo PreprocOptions
forall a. Parser a -> InfoMod a -> ParserInfo a
info (Path Abs Dir -> Parser PreprocOptions
preprocParser Path Abs Dir
cwd) (String -> InfoMod PreprocOptions
forall a. String -> InfoMod a
progDesc String
"Preprocess a source file for use with ghcid"))
Mod CommandFields Command
-> Mod CommandFields Command -> Mod CommandFields Command
forall a. Semigroup a => a -> a -> a
<>
String -> ParserInfo Command -> Mod CommandFields Command
forall a. String -> ParserInfo a -> Mod CommandFields a
command String
"env" (EnvRunnerCommandOptions -> Command
EnvRunner (EnvRunnerCommandOptions -> Command)
-> ParserInfo EnvRunnerCommandOptions -> ParserInfo Command
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser EnvRunnerCommandOptions
-> InfoMod EnvRunnerCommandOptions
-> ParserInfo EnvRunnerCommandOptions
forall a. Parser a -> InfoMod a -> ParserInfo a
info (Path Abs Dir -> Parser EnvRunnerCommandOptions
envParser Path Abs Dir
cwd) (String -> InfoMod EnvRunnerCommandOptions
forall a. String -> InfoMod a
progDesc String
"Print the env runner for a component or a named env"))
Mod CommandFields Command
-> Mod CommandFields Command -> Mod CommandFields Command
forall a. Semigroup a => a -> a -> a
<>
String -> ParserInfo Command -> Mod CommandFields Command
forall a. String -> ParserInfo a -> Mod CommandFields a
command String
"ghci-cmd" (GhciOptions -> Command
GhciCmd (GhciOptions -> Command)
-> ParserInfo GhciOptions -> ParserInfo Command
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser GhciOptions -> InfoMod GhciOptions -> ParserInfo GhciOptions
forall a. Parser a -> InfoMod a -> ParserInfo a
info (Path Abs Dir -> Parser GhciOptions
ghciParser Path Abs Dir
cwd) (String -> InfoMod GhciOptions
forall a. String -> InfoMod a
progDesc String
"Print a ghci cmdline to load a module in a Hix env"))
Mod CommandFields Command
-> Mod CommandFields Command -> Mod CommandFields Command
forall a. Semigroup a => a -> a -> a
<>
String -> ParserInfo Command -> Mod CommandFields Command
forall a. String -> ParserInfo a -> Mod CommandFields a
command String
"ghcid-cmd" (GhcidOptions -> Command
GhcidCmd (GhcidOptions -> Command)
-> ParserInfo GhcidOptions -> ParserInfo Command
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser GhcidOptions
-> InfoMod GhcidOptions -> ParserInfo GhcidOptions
forall a. Parser a -> InfoMod a -> ParserInfo a
info (Path Abs Dir -> Parser GhcidOptions
ghcidParser Path Abs Dir
cwd) (String -> InfoMod GhcidOptions
forall a. String -> InfoMod a
progDesc String
"Print a ghcid cmdline to run a function in a Hix env"))
Mod CommandFields Command
-> Mod CommandFields Command -> Mod CommandFields Command
forall a. Semigroup a => a -> a -> a
<>
String -> ParserInfo Command -> Mod CommandFields Command
forall a. String -> ParserInfo a -> Mod CommandFields a
command String
"new" (NewOptions -> Command
NewCmd (NewOptions -> Command)
-> ParserInfo NewOptions -> ParserInfo Command
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser NewOptions -> InfoMod NewOptions -> ParserInfo NewOptions
forall a. Parser a -> InfoMod a -> ParserInfo a
info Parser NewOptions
newParser (String -> InfoMod NewOptions
forall a. String -> InfoMod a
progDesc String
"Create a new Hix project in the current directory"))
Mod CommandFields Command
-> Mod CommandFields Command -> Mod CommandFields Command
forall a. Semigroup a => a -> a -> a
<>
String -> ParserInfo Command -> Mod CommandFields Command
forall a. String -> ParserInfo a -> Mod CommandFields a
command String
"bootstrap" (BootstrapOptions -> Command
BootstrapCmd (BootstrapOptions -> Command)
-> ParserInfo BootstrapOptions -> ParserInfo Command
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser BootstrapOptions
-> InfoMod BootstrapOptions -> ParserInfo BootstrapOptions
forall a. Parser a -> InfoMod a -> ParserInfo a
info Parser BootstrapOptions
bootstrapParser (String -> InfoMod BootstrapOptions
forall a. String -> InfoMod a
progDesc String
bootstrapDesc))
Mod CommandFields Command
-> Mod CommandFields Command -> Mod CommandFields Command
forall a. Semigroup a => a -> a -> a
<>
String -> ParserInfo Command -> Mod CommandFields Command
forall a. String -> ParserInfo a -> Mod CommandFields a
command String
"bump" (BumpOptions -> Command
BumpCmd (BumpOptions -> Command)
-> ParserInfo BumpOptions -> ParserInfo Command
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser BumpOptions -> InfoMod BumpOptions -> ParserInfo BumpOptions
forall a. Parser a -> InfoMod a -> ParserInfo a
info Parser BumpOptions
bumpParser (String -> InfoMod BumpOptions
forall a. String -> InfoMod a
progDesc String
"Bump the deps of a package"))
Mod CommandFields Command
-> Mod CommandFields Command -> Mod CommandFields Command
forall a. Semigroup a => a -> a -> a
<>
String -> ParserInfo Command -> Mod CommandFields Command
forall a. String -> ParserInfo a -> Mod CommandFields a
command String
"lower" (LowerCommand -> Command
LowerCmd (LowerCommand -> Command)
-> ParserInfo LowerCommand -> ParserInfo Command
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser LowerCommand
-> InfoMod LowerCommand -> ParserInfo LowerCommand
forall a. Parser a -> InfoMod a -> ParserInfo a
info Parser LowerCommand
lowerCommand (String -> InfoMod LowerCommand
forall a. String -> InfoMod a
progDesc String
"Modify the lower bounds of a package"))
where
bootstrapDesc :: String
bootstrapDesc = String
"Bootstrap an existing Cabal project in the current directory"
globalParser ::
Path Abs Dir ->
Parser GlobalOptions
globalParser :: Path Abs Dir -> Parser GlobalOptions
globalParser Path Abs Dir
realCwd = do
Bool
verbose <- Mod FlagFields Bool -> Parser Bool
switch (String -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"verbose" Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<> Char -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => Char -> Mod f a
short Char
'v' 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
"Verbose output")
Bool
debug <- Mod FlagFields Bool -> Parser Bool
switch (String -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"debug" 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
"Debug output")
Bool
quiet <- Mod FlagFields Bool -> Parser Bool
switch (String -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"quiet" 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
"Suppress info output")
Path Abs Dir
cwd <- ReadM (Path Abs Dir)
-> Mod OptionFields (Path Abs Dir) -> Parser (Path Abs Dir)
forall a. ReadM a -> Mod OptionFields a -> Parser a
option ReadM (Path Abs Dir)
absDirOption (String -> Mod OptionFields (Path Abs Dir)
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"cwd" Mod OptionFields (Path Abs Dir)
-> Mod OptionFields (Path Abs Dir)
-> Mod OptionFields (Path Abs Dir)
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields (Path Abs Dir)
forall (f :: * -> *) a. String -> Mod f a
help String
"Force a different working directory" Mod OptionFields (Path Abs Dir)
-> Mod OptionFields (Path Abs Dir)
-> Mod OptionFields (Path Abs Dir)
forall a. Semigroup a => a -> a -> a
<> Path Abs Dir -> Mod OptionFields (Path Abs Dir)
forall (f :: * -> *) a. HasValue f => a -> Mod f a
value Path Abs Dir
realCwd)
OutputFormat
output <- ReadM OutputFormat
-> Mod OptionFields OutputFormat -> Parser OutputFormat
forall a. ReadM a -> Mod OptionFields a -> Parser a
option ReadM OutputFormat
outputFormatOption (String -> Mod OptionFields OutputFormat
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"output" Mod OptionFields OutputFormat
-> Mod OptionFields OutputFormat -> Mod OptionFields OutputFormat
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields OutputFormat
forall (f :: * -> *) a. String -> Mod f a
help String
formatHelp Mod OptionFields OutputFormat
-> Mod OptionFields OutputFormat -> Mod OptionFields OutputFormat
forall a. Semigroup a => a -> a -> a
<> OutputFormat -> Mod OptionFields OutputFormat
forall (f :: * -> *) a. HasValue f => a -> Mod f a
value OutputFormat
OutputNone Mod OptionFields OutputFormat
-> Mod OptionFields OutputFormat -> Mod OptionFields OutputFormat
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields OutputFormat
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
metavar String
"format")
OutputTarget
target <- ReadM OutputTarget
-> Mod OptionFields OutputTarget -> Parser OutputTarget
forall a. ReadM a -> Mod OptionFields a -> Parser a
option ReadM OutputTarget
outputTargetOption (String -> Mod OptionFields OutputTarget
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"target" Mod OptionFields OutputTarget
-> Mod OptionFields OutputTarget -> Mod OptionFields OutputTarget
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields OutputTarget
forall (f :: * -> *) a. String -> Mod f a
help String
targetHelp Mod OptionFields OutputTarget
-> Mod OptionFields OutputTarget -> Mod OptionFields OutputTarget
forall a. Semigroup a => a -> a -> a
<> OutputTarget -> Mod OptionFields OutputTarget
forall (f :: * -> *) a. HasValue f => a -> Mod f a
value OutputTarget
OutputDefault Mod OptionFields OutputTarget
-> Mod OptionFields OutputTarget -> Mod OptionFields OutputTarget
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields OutputTarget
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
metavar String
"target")
pure GlobalOptions {Bool
Path Abs Dir
OutputFormat
OutputTarget
verbose :: Bool
debug :: Bool
quiet :: Bool
cwd :: Path Abs Dir
output :: OutputFormat
target :: OutputTarget
target :: OutputTarget
output :: OutputFormat
cwd :: Path Abs Dir
quiet :: Bool
debug :: Bool
verbose :: Bool
..}
where
formatHelp :: String
formatHelp = String
"Result output format, if commands support it"
targetHelp :: String
targetHelp = String
"Force output to a file or stdout"
appParser ::
Path Abs Dir ->
Parser Options
appParser :: Path Abs Dir -> Parser Options
appParser Path Abs Dir
cwd =
GlobalOptions -> Command -> Options
Options (GlobalOptions -> Command -> Options)
-> Parser GlobalOptions -> Parser (Command -> Options)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Path Abs Dir -> Parser GlobalOptions
globalParser Path Abs Dir
cwd Parser (Command -> Options) -> Parser Command -> Parser Options
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Mod CommandFields Command -> Parser Command
forall a. Mod CommandFields a -> Parser a
hsubparser (Path Abs Dir -> Mod CommandFields Command
commands Path Abs Dir
cwd)
parseCli ::
IO Options
parseCli :: IO Options
parseCli = do
Path Abs Dir
realCwd <- IO (Path Abs Dir)
forall (m :: * -> *). MonadIO m => m (Path Abs Dir)
getCurrentDir
ParserPrefs -> ParserInfo Options -> IO Options
forall a. ParserPrefs -> ParserInfo a -> IO a
customExecParser ParserPrefs
parserPrefs (Parser Options -> InfoMod Options -> ParserInfo Options
forall a. Parser a -> InfoMod a -> ParserInfo a
info (Path Abs Dir -> Parser Options
appParser Path Abs Dir
realCwd Parser Options -> Parser (Options -> Options) -> Parser Options
forall (f :: * -> *) a b. Applicative f => f a -> f (a -> b) -> f b
<**> Parser (Options -> Options)
forall a. Parser (a -> a)
helper) InfoMod Options
forall {a}. InfoMod a
desc)
where
parserPrefs :: ParserPrefs
parserPrefs =
PrefsMod -> ParserPrefs
prefs (PrefsMod
showHelpOnEmpty PrefsMod -> PrefsMod -> PrefsMod
forall a. Semigroup a => a -> a -> a
<> PrefsMod
showHelpOnError PrefsMod -> PrefsMod -> PrefsMod
forall a. Semigroup a => a -> a -> a
<> PrefsMod
subparserInline)
desc :: InfoMod a
desc =
InfoMod a
forall {a}. InfoMod a
fullDesc InfoMod a -> InfoMod a -> InfoMod a
forall a. Semigroup a => a -> a -> a
<> String -> InfoMod a
forall a. String -> InfoMod a
header String
"Tools for maintaining Hix projects"