{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE TemplateHaskell #-}

-- | Copyright: (c) 2021-2022 berberman
-- SPDX-License-Identifier: MIT
-- Maintainer: berberman <berberman@yandex.com>
-- Stability: experimental
-- Portability: portable
--
-- CLI interface of nvfetcher
module NvFetcher.Options
  ( CLIOptions (..),
    Target (..),
    cliOptionsParser,
    getCLIOptions,
  )
where

import Options.Applicative.Simple
import qualified Paths_nvfetcher as Paths

data Target = Build | Clean
  deriving (Target -> Target -> Bool
(Target -> Target -> Bool)
-> (Target -> Target -> Bool) -> Eq Target
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Target -> Target -> Bool
$c/= :: Target -> Target -> Bool
== :: Target -> Target -> Bool
$c== :: Target -> Target -> Bool
Eq)

instance Show Target where
  show :: Target -> String
show Target
Build = String
"build"
  show Target
Clean = String
"clean"

targetParser :: ReadM Target
targetParser :: ReadM Target
targetParser = (String -> Maybe Target) -> ReadM Target
forall a. (String -> Maybe a) -> ReadM a
maybeReader ((String -> Maybe Target) -> ReadM Target)
-> (String -> Maybe Target) -> ReadM Target
forall a b. (a -> b) -> a -> b
$ \case
  String
"build" -> Target -> Maybe Target
forall a. a -> Maybe a
Just Target
Build
  String
"clean" -> Target -> Maybe Target
forall a. a -> Maybe a
Just Target
Clean
  String
_ -> Maybe Target
forall a. Maybe a
Nothing

-- | Options for nvfetcher CLI
data CLIOptions = CLIOptions
  { CLIOptions -> String
optBuildDir :: FilePath,
    CLIOptions -> Bool
optCommit :: Bool,
    CLIOptions -> Maybe String
optLogPath :: Maybe FilePath,
    CLIOptions -> Int
optThreads :: Int,
    CLIOptions -> Int
optRetry :: Int,
    CLIOptions -> Bool
optTiming :: Bool,
    CLIOptions -> Bool
optVerbose :: Bool,
    CLIOptions -> Maybe String
optPkgNameFilter :: Maybe String,
    CLIOptions -> Target
optTarget :: Target
  }
  deriving (Int -> CLIOptions -> ShowS
[CLIOptions] -> ShowS
CLIOptions -> String
(Int -> CLIOptions -> ShowS)
-> (CLIOptions -> String)
-> ([CLIOptions] -> ShowS)
-> Show CLIOptions
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CLIOptions] -> ShowS
$cshowList :: [CLIOptions] -> ShowS
show :: CLIOptions -> String
$cshow :: CLIOptions -> String
showsPrec :: Int -> CLIOptions -> ShowS
$cshowsPrec :: Int -> CLIOptions -> ShowS
Show)

cliOptionsParser :: Parser CLIOptions
cliOptionsParser :: Parser CLIOptions
cliOptionsParser =
  String
-> Bool
-> Maybe String
-> Int
-> Int
-> Bool
-> Bool
-> Maybe String
-> Target
-> CLIOptions
CLIOptions
    (String
 -> Bool
 -> Maybe String
 -> Int
 -> Int
 -> Bool
 -> Bool
 -> Maybe String
 -> Target
 -> CLIOptions)
-> Parser String
-> Parser
     (Bool
      -> Maybe String
      -> Int
      -> Int
      -> Bool
      -> Bool
      -> Maybe String
      -> Target
      -> CLIOptions)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Mod OptionFields String -> Parser String
forall s. IsString s => Mod OptionFields s -> Parser s
strOption
      ( String -> Mod OptionFields String
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"build-dir"
          Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<> Char -> Mod OptionFields String
forall (f :: * -> *) a. HasName f => Char -> Mod f a
short Char
'o'
          Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields String
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
metavar String
"DIR"
          Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields String
forall (f :: * -> *) a. String -> Mod f a
help String
"Directory that nvfetcher puts artifacts to"
          Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<> Mod OptionFields String
forall a (f :: * -> *). Show a => Mod f a
showDefault
          Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields String
forall (f :: * -> *) a. HasValue f => a -> Mod f a
value String
"_sources"
          Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<> Completer -> Mod OptionFields String
forall (f :: * -> *) a. HasCompleter f => Completer -> Mod f a
completer (String -> Completer
bashCompleter String
"directory")
      )
    Parser
  (Bool
   -> Maybe String
   -> Int
   -> Int
   -> Bool
   -> Bool
   -> Maybe String
   -> Target
   -> CLIOptions)
-> Parser Bool
-> Parser
     (Maybe String
      -> Int
      -> Int
      -> Bool
      -> Bool
      -> Maybe String
      -> Target
      -> CLIOptions)
forall (f :: * -> *) a b. Applicative f => 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
"commit-changes"
          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
"`git commit` build dir with version changes as commit message"
      )
    Parser
  (Maybe String
   -> Int
   -> Int
   -> Bool
   -> Bool
   -> Maybe String
   -> Target
   -> CLIOptions)
-> Parser (Maybe String)
-> Parser
     (Int
      -> Int -> Bool -> Bool -> Maybe String -> Target -> CLIOptions)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser String -> Parser (Maybe String)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional
      ( Mod OptionFields String -> Parser String
forall s. IsString s => Mod OptionFields s -> Parser s
strOption
          ( String -> Mod OptionFields String
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"changelog"
              Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<> Char -> Mod OptionFields String
forall (f :: * -> *) a. HasName f => Char -> Mod f a
short Char
'l'
              Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields String
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
metavar String
"FILE"
              Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields String
forall (f :: * -> *) a. String -> Mod f a
help String
"Dump version changes to a file"
              Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<> Completer -> Mod OptionFields String
forall (f :: * -> *) a. HasCompleter f => Completer -> Mod f a
completer (String -> Completer
bashCompleter String
"file")
          )
      )
    Parser
  (Int
   -> Int -> Bool -> Bool -> Maybe String -> Target -> CLIOptions)
-> Parser Int
-> Parser
     (Int -> Bool -> Bool -> Maybe String -> Target -> 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
<> String -> Mod OptionFields Int
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
metavar String
"NUM"
          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
"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 String -> Target -> CLIOptions)
-> Parser Int
-> Parser (Bool -> Bool -> Maybe String -> Target -> 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
<> String -> Mod OptionFields Int
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"retry"
          Mod OptionFields Int
-> Mod OptionFields Int -> Mod OptionFields Int
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields Int
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
metavar String
"NUM"
          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
"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 -> Maybe String -> Target -> CLIOptions)
-> Parser Bool
-> Parser (Bool -> Maybe String -> Target -> CLIOptions)
forall (f :: * -> *) a b. Applicative f => 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
"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
<> String -> Mod FlagFields Bool
forall (f :: * -> *) a. String -> Mod f a
help String
"Show build time")
    Parser (Bool -> Maybe String -> Target -> CLIOptions)
-> Parser Bool -> Parser (Maybe String -> Target -> CLIOptions)
forall (f :: * -> *) a b. Applicative f => 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
"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 mode")
    Parser (Maybe String -> Target -> CLIOptions)
-> Parser (Maybe String) -> Parser (Target -> CLIOptions)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser String -> Parser (Maybe String)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional
      ( Mod OptionFields String -> Parser String
forall s. IsString s => Mod OptionFields s -> Parser s
strOption
          ( Char -> Mod OptionFields String
forall (f :: * -> *) a. HasName f => Char -> Mod f a
short Char
'f'
              Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields String
forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"filter"
              Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields String
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
metavar String
"REGEX"
              Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields String
forall (f :: * -> *) a. String -> Mod f a
help String
"Regex to filter packages to be updated"
          )
      )
    Parser (Target -> CLIOptions) -> Parser Target -> Parser CLIOptions
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
      ( String -> Mod ArgumentFields Target
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
metavar String
"TARGET"
          Mod ArgumentFields Target
-> Mod ArgumentFields Target -> Mod ArgumentFields Target
forall a. Semigroup a => a -> a -> a
<> String -> Mod ArgumentFields Target
forall (f :: * -> *) a. String -> Mod f a
help String
"Two targets are available: 1.build  2.clean"
          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 ([String] -> Completer
listCompleter [Target -> String
forall a. Show a => a -> String
show Target
Build, Target -> String
forall a. Show a => a -> String
show Target
Clean])
          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 :: String
version = $(simpleVersion Paths.version)

-- | Parse nvfetcher CLI options
getCLIOptions :: Parser a -> IO a
getCLIOptions :: Parser a -> IO a
getCLIOptions Parser a
parser = do
  (a
opts, ()) <-
    String
-> String
-> String
-> Parser a
-> ExceptT () (Writer (Mod CommandFields ())) ()
-> IO (a, ())
forall a b.
String
-> String
-> String
-> Parser a
-> ExceptT b (Writer (Mod CommandFields b)) ()
-> IO (a, b)
simpleOptions
      String
version
      String
"nvfetcher"
      String
"generate nix sources expr for the latest version of packages"
      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