{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE TemplateHaskell #-}
module NvFetcher.Options
( CLIOptions (..),
Target (..),
cliOptionsParser,
getCLIOptions,
)
where
import Options.Applicative.Simple
import qualified Paths_nvfetcher as Paths
data Target = Build | Clean | Purge
deriving (Target -> Target -> Bool
(Target -> Target -> Bool)
-> (Target -> Target -> Bool) -> Eq Target
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Target -> Target -> Bool
== :: Target -> Target -> Bool
$c/= :: Target -> Target -> Bool
/= :: Target -> Target -> Bool
Eq)
instance Show Target where
show :: Target -> FilePath
show Target
Build = FilePath
"build"
show Target
Clean = FilePath
"clean"
show Target
Purge = FilePath
"purge"
targetParser :: ReadM Target
targetParser :: ReadM Target
targetParser = (FilePath -> Maybe Target) -> ReadM Target
forall a. (FilePath -> Maybe a) -> ReadM a
maybeReader ((FilePath -> Maybe Target) -> ReadM Target)
-> (FilePath -> Maybe Target) -> ReadM Target
forall a b. (a -> b) -> a -> b
$ \case
FilePath
"build" -> Target -> Maybe Target
forall a. a -> Maybe a
Just Target
Build
FilePath
"clean" -> Target -> Maybe Target
forall a. a -> Maybe a
Just Target
Clean
FilePath
"purge" -> Target -> Maybe Target
forall a. a -> Maybe a
Just Target
Purge
FilePath
_ -> Maybe Target
forall a. Maybe a
Nothing
data CLIOptions = CLIOptions
{ CLIOptions -> FilePath
optBuildDir :: FilePath,
CLIOptions -> Bool
optCommit :: Bool,
CLIOptions -> Maybe FilePath
optCommitSummary :: Maybe String,
CLIOptions -> Maybe FilePath
optLogPath :: Maybe FilePath,
CLIOptions -> Int
optThreads :: Int,
CLIOptions -> Int
optRetry :: Int,
CLIOptions -> Bool
optTiming :: Bool,
CLIOptions -> Bool
optVerbose :: Bool,
CLIOptions -> Maybe FilePath
optPkgNameFilter :: Maybe String,
CLIOptions -> Maybe FilePath
optKeyfile :: Maybe FilePath,
CLIOptions -> Bool
optKeepOldFiles :: Bool,
CLIOptions -> Bool
optKeepGoing :: Bool,
CLIOptions -> Target
optTarget :: Target
}
deriving (Int -> CLIOptions -> ShowS
[CLIOptions] -> ShowS
CLIOptions -> FilePath
(Int -> CLIOptions -> ShowS)
-> (CLIOptions -> FilePath)
-> ([CLIOptions] -> ShowS)
-> Show CLIOptions
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CLIOptions -> ShowS
showsPrec :: Int -> CLIOptions -> ShowS
$cshow :: CLIOptions -> FilePath
show :: CLIOptions -> FilePath
$cshowList :: [CLIOptions] -> ShowS
showList :: [CLIOptions] -> ShowS
Show)
cliOptionsParser :: Parser CLIOptions
cliOptionsParser :: Parser CLIOptions
cliOptionsParser =
FilePath
-> Bool
-> Maybe FilePath
-> Maybe FilePath
-> Int
-> Int
-> Bool
-> Bool
-> Maybe FilePath
-> Maybe FilePath
-> Bool
-> Bool
-> Target
-> CLIOptions
CLIOptions
(FilePath
-> Bool
-> Maybe FilePath
-> Maybe FilePath
-> Int
-> Int
-> Bool
-> Bool
-> Maybe FilePath
-> Maybe FilePath
-> Bool
-> Bool
-> Target
-> CLIOptions)
-> Parser FilePath
-> Parser
(Bool
-> Maybe FilePath
-> Maybe FilePath
-> Int
-> Int
-> Bool
-> Bool
-> Maybe FilePath
-> Maybe FilePath
-> Bool
-> Bool
-> Target
-> CLIOptions)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> 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
"build-dir"
Mod OptionFields FilePath
-> Mod OptionFields FilePath -> Mod OptionFields FilePath
forall a. Semigroup a => a -> a -> a
<> Char -> Mod OptionFields FilePath
forall (f :: * -> *) a. HasName f => Char -> Mod f a
short Char
'o'
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
<> FilePath -> Mod OptionFields FilePath
forall (f :: * -> *) a. FilePath -> Mod f a
help FilePath
"Directory that nvfetcher puts artifacts to"
Mod OptionFields FilePath
-> Mod OptionFields FilePath -> Mod OptionFields FilePath
forall a. Semigroup a => a -> a -> a
<> Mod OptionFields FilePath
forall a (f :: * -> *). Show a => Mod f a
showDefault
Mod OptionFields FilePath
-> Mod OptionFields FilePath -> Mod OptionFields FilePath
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod OptionFields FilePath
forall (f :: * -> *) a. HasValue f => a -> Mod f a
value FilePath
"_sources"
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 (FilePath -> Completer
bashCompleter FilePath
"directory")
)
Parser
(Bool
-> Maybe FilePath
-> Maybe FilePath
-> Int
-> Int
-> Bool
-> Bool
-> Maybe FilePath
-> Maybe FilePath
-> Bool
-> Bool
-> Target
-> CLIOptions)
-> Parser Bool
-> Parser
(Maybe FilePath
-> Maybe FilePath
-> Int
-> Int
-> Bool
-> Bool
-> Maybe FilePath
-> Maybe FilePath
-> Bool
-> Bool
-> Target
-> CLIOptions)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Mod FlagFields Bool -> Parser Bool
switch
( FilePath -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => FilePath -> Mod f a
long FilePath
"commit-changes"
Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod FlagFields Bool
forall (f :: * -> *) a. FilePath -> Mod f a
help FilePath
"`git commit` build dir with version changes as commit message"
)
Parser
(Maybe FilePath
-> Maybe FilePath
-> Int
-> Int
-> Bool
-> Bool
-> Maybe FilePath
-> Maybe FilePath
-> Bool
-> Bool
-> Target
-> CLIOptions)
-> Parser (Maybe FilePath)
-> Parser
(Maybe FilePath
-> Int
-> Int
-> Bool
-> Bool
-> Maybe FilePath
-> Maybe FilePath
-> Bool
-> Bool
-> Target
-> CLIOptions)
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 -> 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
"commit-summary"
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
"SUMMARY"
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
"Summary to use when committing changes"
)
)
Parser
(Maybe FilePath
-> Int
-> Int
-> Bool
-> Bool
-> Maybe FilePath
-> Maybe FilePath
-> Bool
-> Bool
-> Target
-> CLIOptions)
-> Parser (Maybe FilePath)
-> Parser
(Int
-> Int
-> Bool
-> Bool
-> Maybe FilePath
-> Maybe FilePath
-> Bool
-> Bool
-> Target
-> CLIOptions)
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 -> 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
"changelog"
Mod OptionFields FilePath
-> Mod OptionFields FilePath -> Mod OptionFields FilePath
forall a. Semigroup a => a -> a -> a
<> Char -> Mod OptionFields FilePath
forall (f :: * -> *) a. HasName f => Char -> Mod f a
short Char
'l'
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
"FILE"
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
"Dump version changes to a file"
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 (FilePath -> Completer
bashCompleter FilePath
"file")
)
)
Parser
(Int
-> Int
-> Bool
-> Bool
-> Maybe FilePath
-> Maybe FilePath
-> Bool
-> Bool
-> Target
-> CLIOptions)
-> Parser Int
-> Parser
(Int
-> Bool
-> Bool
-> Maybe FilePath
-> Maybe FilePath
-> Bool
-> Bool
-> Target
-> CLIOptions)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> 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
( Char -> Mod OptionFields Int
forall (f :: * -> *) a. HasName f => Char -> Mod f a
short Char
'j'
Mod OptionFields Int
-> Mod OptionFields Int -> Mod OptionFields Int
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod OptionFields Int
forall (f :: * -> *) a. HasMetavar f => FilePath -> Mod f a
metavar FilePath
"NUM"
Mod OptionFields Int
-> Mod OptionFields Int -> Mod OptionFields Int
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod OptionFields Int
forall (f :: * -> *) a. FilePath -> Mod f a
help FilePath
"Number of threads (0: detected number of processors)"
Mod OptionFields Int
-> Mod OptionFields Int -> Mod OptionFields Int
forall a. Semigroup a => a -> a -> a
<> Int -> Mod OptionFields Int
forall (f :: * -> *) a. HasValue f => a -> Mod f a
value Int
0
Mod OptionFields Int
-> Mod OptionFields Int -> Mod OptionFields Int
forall a. Semigroup a => a -> a -> a
<> Mod OptionFields Int
forall a (f :: * -> *). Show a => Mod f a
showDefault
)
Parser
(Int
-> Bool
-> Bool
-> Maybe FilePath
-> Maybe FilePath
-> Bool
-> Bool
-> Target
-> CLIOptions)
-> Parser Int
-> Parser
(Bool
-> Bool
-> Maybe FilePath
-> Maybe FilePath
-> Bool
-> Bool
-> Target
-> CLIOptions)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> 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
( Char -> Mod OptionFields Int
forall (f :: * -> *) a. HasName f => Char -> Mod f a
short Char
'r'
Mod OptionFields Int
-> Mod OptionFields Int -> Mod OptionFields Int
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod OptionFields Int
forall (f :: * -> *) a. HasName f => FilePath -> Mod f a
long FilePath
"retry"
Mod OptionFields Int
-> Mod OptionFields Int -> Mod OptionFields Int
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod OptionFields Int
forall (f :: * -> *) a. HasMetavar f => FilePath -> Mod f a
metavar FilePath
"NUM"
Mod OptionFields Int
-> Mod OptionFields Int -> Mod OptionFields Int
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod OptionFields Int
forall (f :: * -> *) a. FilePath -> Mod f a
help FilePath
"Times to retry of some rules (nvchecker, prefetch, nix-build, etc.)"
Mod OptionFields Int
-> Mod OptionFields Int -> Mod OptionFields Int
forall a. Semigroup a => a -> a -> a
<> Int -> Mod OptionFields Int
forall (f :: * -> *) a. HasValue f => a -> Mod f a
value Int
3
Mod OptionFields Int
-> Mod OptionFields Int -> Mod OptionFields Int
forall a. Semigroup a => a -> a -> a
<> Mod OptionFields Int
forall a (f :: * -> *). Show a => Mod f a
showDefault
)
Parser
(Bool
-> Bool
-> Maybe FilePath
-> Maybe FilePath
-> Bool
-> Bool
-> Target
-> CLIOptions)
-> Parser Bool
-> Parser
(Bool
-> Maybe FilePath
-> Maybe FilePath
-> Bool
-> Bool
-> Target
-> CLIOptions)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Mod FlagFields Bool -> Parser Bool
switch (FilePath -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => FilePath -> Mod f a
long FilePath
"timing" 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
't' Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod FlagFields Bool
forall (f :: * -> *) a. FilePath -> Mod f a
help FilePath
"Show build time")
Parser
(Bool
-> Maybe FilePath
-> Maybe FilePath
-> Bool
-> Bool
-> Target
-> CLIOptions)
-> Parser Bool
-> Parser
(Maybe FilePath
-> Maybe FilePath -> Bool -> Bool -> Target -> CLIOptions)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Mod FlagFields Bool -> Parser Bool
switch (FilePath -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => FilePath -> Mod f a
long FilePath
"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
<> FilePath -> Mod FlagFields Bool
forall (f :: * -> *) a. FilePath -> Mod f a
help FilePath
"Verbose mode")
Parser
(Maybe FilePath
-> Maybe FilePath -> Bool -> Bool -> Target -> CLIOptions)
-> Parser (Maybe FilePath)
-> Parser (Maybe FilePath -> Bool -> Bool -> Target -> CLIOptions)
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 -> 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
( Char -> Mod OptionFields FilePath
forall (f :: * -> *) a. HasName f => Char -> Mod f a
short Char
'f'
Mod OptionFields FilePath
-> Mod OptionFields FilePath -> Mod OptionFields FilePath
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod OptionFields FilePath
forall (f :: * -> *) a. HasName f => FilePath -> Mod f a
long FilePath
"filter"
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
"REGEX"
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
"Regex to filter packages to be updated"
)
)
Parser (Maybe FilePath -> Bool -> Bool -> Target -> CLIOptions)
-> Parser (Maybe FilePath)
-> Parser (Bool -> Bool -> Target -> CLIOptions)
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 -> 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
( Char -> Mod OptionFields FilePath
forall (f :: * -> *) a. HasName f => Char -> Mod f a
short Char
'k'
Mod OptionFields FilePath
-> Mod OptionFields FilePath -> Mod OptionFields FilePath
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod OptionFields FilePath
forall (f :: * -> *) a. HasName f => FilePath -> Mod f a
long FilePath
"keyfile"
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
"FILE"
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
"Nvchecker keyfile"
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 (FilePath -> Completer
bashCompleter FilePath
"file")
)
)
Parser (Bool -> Bool -> Target -> CLIOptions)
-> Parser Bool -> Parser (Bool -> Target -> CLIOptions)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Mod FlagFields Bool -> Parser Bool
switch (FilePath -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => FilePath -> Mod f a
long FilePath
"keep-old" Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod FlagFields Bool
forall (f :: * -> *) a. FilePath -> Mod f a
help FilePath
"Don't remove old files other than generated json and nix before build")
Parser (Bool -> Target -> CLIOptions)
-> Parser Bool -> Parser (Target -> CLIOptions)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Mod FlagFields Bool -> Parser Bool
switch (FilePath -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => FilePath -> Mod f a
long FilePath
"keep-going" Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod FlagFields Bool
forall (f :: * -> *) a. FilePath -> Mod f a
help FilePath
"Don't stop if some packages failed to be fetched")
Parser (Target -> CLIOptions) -> Parser Target -> Parser CLIOptions
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ReadM Target -> Mod ArgumentFields Target -> Parser Target
forall a. ReadM a -> Mod ArgumentFields a -> Parser a
argument
ReadM Target
targetParser
( FilePath -> Mod ArgumentFields Target
forall (f :: * -> *) a. HasMetavar f => FilePath -> Mod f a
metavar FilePath
"TARGET"
Mod ArgumentFields Target
-> Mod ArgumentFields Target -> Mod ArgumentFields Target
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod ArgumentFields Target
forall (f :: * -> *) a. FilePath -> Mod f a
help FilePath
"Three targets are available: 1.build 2.clean (remove all generated files) 3.purge (remove shake db)"
Mod ArgumentFields Target
-> Mod ArgumentFields Target -> Mod ArgumentFields Target
forall a. Semigroup a => a -> a -> a
<> Target -> Mod ArgumentFields Target
forall (f :: * -> *) a. HasValue f => a -> Mod f a
value Target
Build
Mod ArgumentFields Target
-> Mod ArgumentFields Target -> Mod ArgumentFields Target
forall a. Semigroup a => a -> a -> a
<> Completer -> Mod ArgumentFields Target
forall (f :: * -> *) a. HasCompleter f => Completer -> Mod f a
completer ([FilePath] -> Completer
listCompleter [Target -> FilePath
forall a. Show a => a -> FilePath
show Target
Build, Target -> FilePath
forall a. Show a => a -> FilePath
show Target
Clean, Target -> FilePath
forall a. Show a => a -> FilePath
show Target
Purge])
Mod ArgumentFields Target
-> Mod ArgumentFields Target -> Mod ArgumentFields Target
forall a. Semigroup a => a -> a -> a
<> Mod ArgumentFields Target
forall a (f :: * -> *). Show a => Mod f a
showDefault
)
version :: String
version :: FilePath
version = $(simpleVersion Paths.version)
getCLIOptions :: Parser a -> IO a
getCLIOptions :: forall a. Parser a -> IO a
getCLIOptions Parser a
parser = do
(a
opts, ()) <-
FilePath
-> FilePath
-> FilePath
-> Parser a
-> ExceptT () (Writer (Mod CommandFields ())) ()
-> IO (a, ())
forall a b.
FilePath
-> FilePath
-> FilePath
-> Parser a
-> ExceptT b (Writer (Mod CommandFields b)) ()
-> IO (a, b)
simpleOptions
FilePath
version
FilePath
"nvfetcher"
FilePath
"generate nix sources expr for the latest version of packages"
Parser a
parser
ExceptT () (Writer (Mod CommandFields ())) ()
forall a. ExceptT () (Writer (Mod CommandFields ())) a
forall (f :: * -> *) a. Alternative f => f a
empty
a -> IO a
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure a
opts