{-# LANGUAGE TemplateHaskell #-}
module NvFetcher.Options
( CLIOptions (..),
cliOptionsParser,
getCLIOptions,
)
where
import Options.Applicative.Simple
import qualified Paths_nvfetcher as Paths
data CLIOptions = CLIOptions
{ CLIOptions -> FilePath
outputPath :: FilePath,
CLIOptions -> Maybe FilePath
logPath :: Maybe FilePath,
CLIOptions -> Int
threads :: Int,
CLIOptions -> Int
retries :: Int,
CLIOptions -> Bool
timing :: Bool,
CLIOptions -> Bool
verbose :: Bool,
CLIOptions -> FilePath
target :: String
}
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
showList :: [CLIOptions] -> ShowS
$cshowList :: [CLIOptions] -> ShowS
show :: CLIOptions -> FilePath
$cshow :: CLIOptions -> FilePath
showsPrec :: Int -> CLIOptions -> ShowS
$cshowsPrec :: Int -> CLIOptions -> ShowS
Show)
cliOptionsParser :: Parser CLIOptions
cliOptionsParser :: Parser CLIOptions
cliOptionsParser =
FilePath
-> Maybe FilePath
-> Int
-> Int
-> Bool
-> Bool
-> FilePath
-> CLIOptions
CLIOptions
(FilePath
-> Maybe FilePath
-> Int
-> Int
-> Bool
-> Bool
-> FilePath
-> CLIOptions)
-> Parser FilePath
-> Parser
(Maybe FilePath
-> Int -> Int -> Bool -> Bool -> FilePath -> 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
"output"
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
"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
"Path to output nix file"
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.nix"
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
(Maybe FilePath
-> Int -> Int -> Bool -> Bool -> FilePath -> CLIOptions)
-> Parser (Maybe FilePath)
-> Parser (Int -> Int -> Bool -> Bool -> FilePath -> CLIOptions)
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 -> FilePath -> CLIOptions)
-> Parser Int
-> Parser (Int -> Bool -> Bool -> FilePath -> CLIOptions)
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 -> FilePath -> CLIOptions)
-> Parser Int -> Parser (Bool -> Bool -> FilePath -> CLIOptions)
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-instantiate, 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 -> FilePath -> CLIOptions)
-> Parser Bool -> Parser (Bool -> FilePath -> CLIOptions)
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 -> FilePath -> CLIOptions)
-> Parser Bool -> Parser (FilePath -> CLIOptions)
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 (FilePath -> CLIOptions)
-> Parser FilePath -> Parser CLIOptions
forall (f :: * -> *) a b. Applicative f => 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
"TARGET"
Mod ArgumentFields FilePath
-> Mod ArgumentFields FilePath -> Mod ArgumentFields FilePath
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod ArgumentFields FilePath
forall (f :: * -> *) a. FilePath -> Mod f a
help FilePath
"Two targets are available: 1.build 2.clean"
Mod ArgumentFields FilePath
-> Mod ArgumentFields FilePath -> Mod ArgumentFields FilePath
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod ArgumentFields FilePath
forall (f :: * -> *) a. HasValue f => a -> Mod f a
value FilePath
"build"
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 ([FilePath] -> Completer
listCompleter [FilePath
"build", FilePath
"clean"])
Mod ArgumentFields FilePath
-> Mod ArgumentFields FilePath -> Mod ArgumentFields FilePath
forall a. Semigroup a => a -> a -> a
<> Mod ArgumentFields FilePath
forall a (f :: * -> *). Show a => Mod f a
showDefault
)
version :: String
version :: FilePath
version = $(simpleVersion Paths.version)
getCLIOptions :: Parser a -> IO a
getCLIOptions :: 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 - generate nix sources expr for the latest version of packages"
( [FilePath] -> FilePath
unlines
[ FilePath
"It's important to keep _build dir.",
FilePath
"If you change any field of an existing package, you may have to run target \"clean\" to invalidate the databse,",
FilePath
"making sure the consistency of our build system."
]
)
Parser a
parser
ExceptT () (Writer (Mod CommandFields ())) ()
forall (f :: * -> *) a. Alternative f => f a
empty
a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure a
opts