{-# LANGUAGE CPP #-}
module HaskellCI.Cli where
import HaskellCI.Prelude
import System.Exit (exitFailure)
import System.FilePath.Posix (takeFileName)
import System.IO (hPutStrLn, stderr)
import qualified Options.Applicative as O
import HaskellCI.Config
import HaskellCI.OptparseGrammar
import HaskellCI.VersionInfo
data Command
= CommandTravis FilePath
| CommandBash FilePath
| CommandGitHub FilePath
| CommandRegenerate
| CommandListGHC
| CommandDumpConfig
| CommandVersionInfo
deriving Int -> Command -> ShowS
[Command] -> ShowS
Command -> FilePath
(Int -> Command -> ShowS)
-> (Command -> FilePath) -> ([Command] -> ShowS) -> Show Command
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Command -> ShowS
showsPrec :: Int -> Command -> ShowS
$cshow :: Command -> FilePath
show :: Command -> FilePath
$cshowList :: [Command] -> ShowS
showList :: [Command] -> ShowS
Show
data Options = Options
{ Options -> Maybe Output
optOutput :: Maybe Output
, Options -> ConfigOpt
optConfig :: ConfigOpt
, Options -> Maybe FilePath
optCwd :: Maybe FilePath
, Options -> Maybe InputType
optInputType :: Maybe InputType
, Options -> Config -> Config
optConfigMorphism :: Config -> Config
}
instance Semigroup Options where
Options Maybe Output
b ConfigOpt
d Maybe FilePath
c Maybe InputType
e Config -> Config
f <> :: Options -> Options -> Options
<> Options Maybe Output
b' ConfigOpt
d' Maybe FilePath
c' Maybe InputType
e' Config -> Config
f' =
Maybe Output
-> ConfigOpt
-> Maybe FilePath
-> Maybe InputType
-> (Config -> Config)
-> Options
Options (Maybe Output
b Maybe Output -> Maybe Output -> Maybe Output
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Maybe Output
b') (ConfigOpt
d ConfigOpt -> ConfigOpt -> ConfigOpt
forall a. Semigroup a => a -> a -> a
<> ConfigOpt
d') (Maybe FilePath
c Maybe FilePath -> Maybe FilePath -> Maybe FilePath
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Maybe FilePath
c') (Maybe InputType
e Maybe InputType -> Maybe InputType -> Maybe InputType
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Maybe InputType
e') (Config -> Config
f' (Config -> Config) -> (Config -> Config) -> Config -> Config
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Config -> Config
f)
defaultOptions :: Options
defaultOptions :: Options
defaultOptions = Options
{ optOutput :: Maybe Output
optOutput = Maybe Output
forall a. Maybe a
Nothing
, optConfig :: ConfigOpt
optConfig = ConfigOpt
ConfigOptAuto
, optCwd :: Maybe FilePath
optCwd = Maybe FilePath
forall a. Maybe a
Nothing
, optInputType :: Maybe InputType
optInputType = Maybe InputType
forall a. Maybe a
Nothing
, optConfigMorphism :: Config -> Config
optConfigMorphism = Config -> Config
forall a. a -> a
id
}
optionsWithOutputFile :: FilePath -> Options
optionsWithOutputFile :: FilePath -> Options
optionsWithOutputFile FilePath
fp = Options
defaultOptions
{ optOutput = Just (OutputFile fp)
}
data Output = OutputStdout | OutputFile FilePath
data ConfigOpt
= ConfigOptAuto
| ConfigOpt FilePath
| ConfigOptNo
deriving (ConfigOpt -> ConfigOpt -> Bool
(ConfigOpt -> ConfigOpt -> Bool)
-> (ConfigOpt -> ConfigOpt -> Bool) -> Eq ConfigOpt
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ConfigOpt -> ConfigOpt -> Bool
== :: ConfigOpt -> ConfigOpt -> Bool
$c/= :: ConfigOpt -> ConfigOpt -> Bool
/= :: ConfigOpt -> ConfigOpt -> Bool
Eq, Int -> ConfigOpt -> ShowS
[ConfigOpt] -> ShowS
ConfigOpt -> FilePath
(Int -> ConfigOpt -> ShowS)
-> (ConfigOpt -> FilePath)
-> ([ConfigOpt] -> ShowS)
-> Show ConfigOpt
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ConfigOpt -> ShowS
showsPrec :: Int -> ConfigOpt -> ShowS
$cshow :: ConfigOpt -> FilePath
show :: ConfigOpt -> FilePath
$cshowList :: [ConfigOpt] -> ShowS
showList :: [ConfigOpt] -> ShowS
Show)
instance Semigroup ConfigOpt where
ConfigOpt
a <> :: ConfigOpt -> ConfigOpt -> ConfigOpt
<> ConfigOpt
ConfigOptAuto = ConfigOpt
a
ConfigOpt
_ <> ConfigOpt
b = ConfigOpt
b
data InputType
= InputTypePackage
| InputTypeProject
deriving Int -> InputType -> ShowS
[InputType] -> ShowS
InputType -> FilePath
(Int -> InputType -> ShowS)
-> (InputType -> FilePath)
-> ([InputType] -> ShowS)
-> Show InputType
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> InputType -> ShowS
showsPrec :: Int -> InputType -> ShowS
$cshow :: InputType -> FilePath
show :: InputType -> FilePath
$cshowList :: [InputType] -> ShowS
showList :: [InputType] -> ShowS
Show
optInputType' :: Options -> FilePath -> InputType
optInputType' :: Options -> FilePath -> InputType
optInputType' Options
opts FilePath
path =
InputType -> Maybe InputType -> InputType
forall a. a -> Maybe a -> a
fromMaybe InputType
def (Options -> Maybe InputType
optInputType Options
opts)
where
def :: InputType
def | FilePath
"cabal.project" FilePath -> FilePath -> Bool
forall a. Eq a => [a] -> [a] -> Bool
`isPrefixOf` ShowS
takeFileName FilePath
path = InputType
InputTypeProject
| Bool
otherwise = InputType
InputTypePackage
optionsP :: O.Parser Options
optionsP :: Parser Options
optionsP = Maybe Output
-> ConfigOpt
-> Maybe FilePath
-> Maybe InputType
-> (Config -> Config)
-> Options
Options
(Maybe Output
-> ConfigOpt
-> Maybe FilePath
-> Maybe InputType
-> (Config -> Config)
-> Options)
-> Parser (Maybe Output)
-> Parser
(ConfigOpt
-> Maybe FilePath
-> Maybe InputType
-> (Config -> Config)
-> Options)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Output -> Parser (Maybe Output)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
O.optional Parser Output
outputP
Parser
(ConfigOpt
-> Maybe FilePath
-> Maybe InputType
-> (Config -> Config)
-> Options)
-> Parser ConfigOpt
-> Parser
(Maybe FilePath
-> Maybe InputType -> (Config -> Config) -> Options)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser ConfigOpt
configOptP
Parser
(Maybe FilePath
-> Maybe InputType -> (Config -> Config) -> Options)
-> Parser (Maybe FilePath)
-> Parser (Maybe InputType -> (Config -> Config) -> Options)
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)
O.optional (Mod OptionFields FilePath -> Parser FilePath
forall s. IsString s => Mod OptionFields s -> Parser s
O.strOption (FilePath -> Mod OptionFields FilePath
forall (f :: * -> *) a. HasName f => FilePath -> Mod f a
O.long FilePath
"cwd" Mod OptionFields FilePath
-> Mod OptionFields FilePath -> Mod OptionFields FilePath
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod OptionFields FilePath
forall (f :: * -> *) a. HasMetavar f => FilePath -> Mod f a
O.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. HasCompleter f => FilePath -> Mod f a
O.action FilePath
"directory" 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
O.help FilePath
"Directory to change to"))
Parser (Maybe InputType -> (Config -> Config) -> Options)
-> Parser (Maybe InputType)
-> Parser ((Config -> Config) -> Options)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser InputType -> Parser (Maybe InputType)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
O.optional Parser InputType
inputTypeP
Parser ((Config -> Config) -> Options)
-> Parser (Config -> Config) -> 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
<*> OptparseGrammar Config Config -> Parser (Config -> Config)
forall s a. OptparseGrammar s a -> Parser (s -> s)
runOptparseGrammar OptparseGrammar Config Config
forall (c :: * -> Constraint) (g :: * -> * -> *).
(OptionsGrammar c g, Applicative (g Config), c (Identity HLintJob),
c (Identity PackageScope), c (Identity TestedWithJobs),
c (Identity Ubuntu), c (Identity Jobs), c (Identity CopyFields),
c (Identity Version), c (Identity Natural),
c (Identity Components), c Env, c Folds, c CopyFields,
c HeadVersion, c (List FSep (Identity Installed) Installed),
Applicative (g DoctestConfig), Applicative (g DocspecConfig),
Applicative (g HLintConfig)) =>
g Config Config
configGrammar
configOptP :: O.Parser ConfigOpt
configOptP :: Parser ConfigOpt
configOptP = Parser ConfigOpt
file Parser ConfigOpt -> Parser ConfigOpt -> Parser ConfigOpt
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Parser ConfigOpt
noconfig Parser ConfigOpt -> Parser ConfigOpt -> Parser ConfigOpt
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ConfigOpt -> Parser ConfigOpt
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ConfigOpt
ConfigOptAuto
where
file :: Parser ConfigOpt
file = FilePath -> ConfigOpt
ConfigOpt (FilePath -> ConfigOpt) -> Parser FilePath -> Parser ConfigOpt
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
O.strOption (FilePath -> Mod OptionFields FilePath
forall (f :: * -> *) a. HasName f => FilePath -> Mod f a
O.long FilePath
"config" 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
O.metavar FilePath
"CONFIGFILE" Mod OptionFields FilePath
-> Mod OptionFields FilePath -> Mod OptionFields FilePath
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod OptionFields FilePath
forall (f :: * -> *) a. HasCompleter f => FilePath -> Mod f a
O.action 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
O.help FilePath
"Configuration file")
noconfig :: Parser ConfigOpt
noconfig = ConfigOpt -> Mod FlagFields ConfigOpt -> Parser ConfigOpt
forall a. a -> Mod FlagFields a -> Parser a
O.flag' ConfigOpt
ConfigOptNo (FilePath -> Mod FlagFields ConfigOpt
forall (f :: * -> *) a. HasName f => FilePath -> Mod f a
O.long FilePath
"no-config" Mod FlagFields ConfigOpt
-> Mod FlagFields ConfigOpt -> Mod FlagFields ConfigOpt
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod FlagFields ConfigOpt
forall (f :: * -> *) a. FilePath -> Mod f a
O.help FilePath
"Don't read configuration file")
outputP :: O.Parser Output
outputP :: Parser Output
outputP =
FilePath -> Output
OutputFile (FilePath -> Output) -> Parser FilePath -> Parser Output
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
O.strOption (FilePath -> Mod OptionFields FilePath
forall (f :: * -> *) a. HasName f => FilePath -> Mod f a
O.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
O.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
O.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. HasCompleter f => FilePath -> Mod f a
O.action 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
O.help FilePath
"Output file") Parser Output -> Parser Output -> Parser Output
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
Output -> Mod FlagFields Output -> Parser Output
forall a. a -> Mod FlagFields a -> Parser a
O.flag' Output
OutputStdout (FilePath -> Mod FlagFields Output
forall (f :: * -> *) a. HasName f => FilePath -> Mod f a
O.long FilePath
"stdout" Mod FlagFields Output
-> Mod FlagFields Output -> Mod FlagFields Output
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod FlagFields Output
forall (f :: * -> *) a. FilePath -> Mod f a
O.help FilePath
"Use stdout output")
versionP :: O.Parser (a -> a)
versionP :: forall a. Parser (a -> a)
versionP = FilePath -> Mod OptionFields (a -> a) -> Parser (a -> a)
forall a. FilePath -> Mod OptionFields (a -> a) -> Parser (a -> a)
O.infoOption FilePath
haskellCIVerStr (Mod OptionFields (a -> a) -> Parser (a -> a))
-> Mod OptionFields (a -> a) -> Parser (a -> a)
forall a b. (a -> b) -> a -> b
$ [Mod OptionFields (a -> a)] -> Mod OptionFields (a -> a)
forall a. Monoid a => [a] -> a
mconcat
[ FilePath -> Mod OptionFields (a -> a)
forall (f :: * -> *) a. HasName f => FilePath -> Mod f a
O.long FilePath
"version"
, Char -> Mod OptionFields (a -> a)
forall (f :: * -> *) a. HasName f => Char -> Mod f a
O.short Char
'V'
, FilePath -> Mod OptionFields (a -> a)
forall (f :: * -> *) a. FilePath -> Mod f a
O.help FilePath
"Print version information"
]
inputTypeP :: O.Parser InputType
inputTypeP :: Parser InputType
inputTypeP = Parser InputType
pkg Parser InputType -> Parser InputType -> Parser InputType
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Parser InputType
prj where
pkg :: Parser InputType
pkg = InputType -> Mod FlagFields InputType -> Parser InputType
forall a. a -> Mod FlagFields a -> Parser a
O.flag' InputType
InputTypePackage (Mod FlagFields InputType -> Parser InputType)
-> Mod FlagFields InputType -> Parser InputType
forall a b. (a -> b) -> a -> b
$ FilePath -> Mod FlagFields InputType
forall (f :: * -> *) a. HasName f => FilePath -> Mod f a
O.long FilePath
"package"
prj :: Parser InputType
prj = InputType -> Mod FlagFields InputType -> Parser InputType
forall a. a -> Mod FlagFields a -> Parser a
O.flag' InputType
InputTypeProject (Mod FlagFields InputType -> Parser InputType)
-> Mod FlagFields InputType -> Parser InputType
forall a b. (a -> b) -> a -> b
$ FilePath -> Mod FlagFields InputType
forall (f :: * -> *) a. HasName f => FilePath -> Mod f a
O.long FilePath
"project"
cliParserInfo :: O.ParserInfo (Command, Options)
cliParserInfo :: ParserInfo (Command, Options)
cliParserInfo = Parser (Command, Options)
-> InfoMod (Command, Options) -> ParserInfo (Command, Options)
forall a. Parser a -> InfoMod a -> ParserInfo a
O.info ((,) (Command -> Options -> (Command, Options))
-> Parser Command -> Parser (Options -> (Command, Options))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Command
cmdP Parser (Options -> (Command, Options))
-> Parser Options -> Parser (Command, Options)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Options
optionsP Parser (Command, Options)
-> Parser ((Command, Options) -> (Command, Options))
-> Parser (Command, Options)
forall (f :: * -> *) a b. Applicative f => f a -> f (a -> b) -> f b
O.<**> Parser ((Command, Options) -> (Command, Options))
forall a. Parser (a -> a)
versionP Parser (Command, Options)
-> Parser ((Command, Options) -> (Command, Options))
-> Parser (Command, Options)
forall (f :: * -> *) a b. Applicative f => f a -> f (a -> b) -> f b
O.<**> Parser ((Command, Options) -> (Command, Options))
forall a. Parser (a -> a)
O.helper) (InfoMod (Command, Options) -> ParserInfo (Command, Options))
-> InfoMod (Command, Options) -> ParserInfo (Command, Options)
forall a b. (a -> b) -> a -> b
$ [InfoMod (Command, Options)] -> InfoMod (Command, Options)
forall a. Monoid a => [a] -> a
mconcat
[ InfoMod (Command, Options)
forall a. InfoMod a
O.fullDesc
, FilePath -> InfoMod (Command, Options)
forall a. FilePath -> InfoMod a
O.header FilePath
"haskell-ci - generate CI scripts for Haskell projects"
]
where
cmdP :: Parser Command
cmdP = Mod CommandFields Command -> Parser Command
forall a. Mod CommandFields a -> Parser a
O.subparser ([Mod CommandFields Command] -> Mod CommandFields Command
forall a. Monoid a => [a] -> a
mconcat
[ FilePath -> ParserInfo Command -> Mod CommandFields Command
forall a. FilePath -> ParserInfo a -> Mod CommandFields a
O.command FilePath
"regenerate" (ParserInfo Command -> Mod CommandFields Command)
-> ParserInfo Command -> Mod CommandFields Command
forall a b. (a -> b) -> a -> b
$ Parser Command -> InfoMod Command -> ParserInfo Command
forall a. Parser a -> InfoMod a -> ParserInfo a
O.info (Command -> Parser Command
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Command
CommandRegenerate) (InfoMod Command -> ParserInfo Command)
-> InfoMod Command -> ParserInfo Command
forall a b. (a -> b) -> a -> b
$ FilePath -> InfoMod Command
forall a. FilePath -> InfoMod a
O.progDesc FilePath
"Regenerate outputs"
, FilePath -> ParserInfo Command -> Mod CommandFields Command
forall a. FilePath -> ParserInfo a -> Mod CommandFields a
O.command FilePath
"travis" (ParserInfo Command -> Mod CommandFields Command)
-> ParserInfo Command -> Mod CommandFields Command
forall a b. (a -> b) -> a -> b
$ Parser Command -> InfoMod Command -> ParserInfo Command
forall a. Parser a -> InfoMod a -> ParserInfo a
O.info Parser Command
travisP (InfoMod Command -> ParserInfo Command)
-> InfoMod Command -> ParserInfo Command
forall a b. (a -> b) -> a -> b
$ FilePath -> InfoMod Command
forall a. FilePath -> InfoMod a
O.progDesc FilePath
"Generate travis-ci config"
, FilePath -> ParserInfo Command -> Mod CommandFields Command
forall a. FilePath -> ParserInfo a -> Mod CommandFields a
O.command FilePath
"bash" (ParserInfo Command -> Mod CommandFields Command)
-> ParserInfo Command -> Mod CommandFields Command
forall a b. (a -> b) -> a -> b
$ Parser Command -> InfoMod Command -> ParserInfo Command
forall a. Parser a -> InfoMod a -> ParserInfo a
O.info Parser Command
bashP (InfoMod Command -> ParserInfo Command)
-> InfoMod Command -> ParserInfo Command
forall a b. (a -> b) -> a -> b
$ FilePath -> InfoMod Command
forall a. FilePath -> InfoMod a
O.progDesc FilePath
"Generate local-bash-docker script"
, FilePath -> ParserInfo Command -> Mod CommandFields Command
forall a. FilePath -> ParserInfo a -> Mod CommandFields a
O.command FilePath
"github" (ParserInfo Command -> Mod CommandFields Command)
-> ParserInfo Command -> Mod CommandFields Command
forall a b. (a -> b) -> a -> b
$ Parser Command -> InfoMod Command -> ParserInfo Command
forall a. Parser a -> InfoMod a -> ParserInfo a
O.info Parser Command
githubP (InfoMod Command -> ParserInfo Command)
-> InfoMod Command -> ParserInfo Command
forall a b. (a -> b) -> a -> b
$ FilePath -> InfoMod Command
forall a. FilePath -> InfoMod a
O.progDesc FilePath
"Generate GitHub Actions config"
, FilePath -> ParserInfo Command -> Mod CommandFields Command
forall a. FilePath -> ParserInfo a -> Mod CommandFields a
O.command FilePath
"list-ghc" (ParserInfo Command -> Mod CommandFields Command)
-> ParserInfo Command -> Mod CommandFields Command
forall a b. (a -> b) -> a -> b
$ Parser Command -> InfoMod Command -> ParserInfo Command
forall a. Parser a -> InfoMod a -> ParserInfo a
O.info (Command -> Parser Command
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Command
CommandListGHC) (InfoMod Command -> ParserInfo Command)
-> InfoMod Command -> ParserInfo Command
forall a b. (a -> b) -> a -> b
$ FilePath -> InfoMod Command
forall a. FilePath -> InfoMod a
O.progDesc FilePath
"List known GHC versions"
, FilePath -> ParserInfo Command -> Mod CommandFields Command
forall a. FilePath -> ParserInfo a -> Mod CommandFields a
O.command FilePath
"dump-config" (ParserInfo Command -> Mod CommandFields Command)
-> ParserInfo Command -> Mod CommandFields Command
forall a b. (a -> b) -> a -> b
$ Parser Command -> InfoMod Command -> ParserInfo Command
forall a. Parser a -> InfoMod a -> ParserInfo a
O.info (Command -> Parser Command
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Command
CommandDumpConfig) (InfoMod Command -> ParserInfo Command)
-> InfoMod Command -> ParserInfo Command
forall a b. (a -> b) -> a -> b
$ FilePath -> InfoMod Command
forall a. FilePath -> InfoMod a
O.progDesc FilePath
"Dump cabal.haskell-ci config with default values"
, FilePath -> ParserInfo Command -> Mod CommandFields Command
forall a. FilePath -> ParserInfo a -> Mod CommandFields a
O.command FilePath
"version-info" (ParserInfo Command -> Mod CommandFields Command)
-> ParserInfo Command -> Mod CommandFields Command
forall a b. (a -> b) -> a -> b
$ Parser Command -> InfoMod Command -> ParserInfo Command
forall a. Parser a -> InfoMod a -> ParserInfo a
O.info (Command -> Parser Command
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Command
CommandVersionInfo) (InfoMod Command -> ParserInfo Command)
-> InfoMod Command -> ParserInfo Command
forall a b. (a -> b) -> a -> b
$ FilePath -> InfoMod Command
forall a. FilePath -> InfoMod a
O.progDesc FilePath
"Print versions info haskell-ci was compiled with"
]) Parser Command -> Parser Command -> Parser Command
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Parser Command
travisP
travisP :: Parser Command
travisP = FilePath -> Command
CommandTravis
(FilePath -> Command) -> Parser FilePath -> Parser Command
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Mod ArgumentFields FilePath -> Parser FilePath
forall s. IsString s => Mod ArgumentFields s -> Parser s
O.strArgument (FilePath -> Mod ArgumentFields FilePath
forall (f :: * -> *) a. HasMetavar f => FilePath -> Mod f a
O.metavar FilePath
"CABAL.FILE" Mod ArgumentFields FilePath
-> Mod ArgumentFields FilePath -> Mod ArgumentFields FilePath
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod ArgumentFields FilePath
forall (f :: * -> *) a. HasCompleter f => FilePath -> Mod f a
O.action FilePath
"file" 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
O.help FilePath
"Either <pkg.cabal> or cabal.project")
bashP :: Parser Command
bashP = FilePath -> Command
CommandBash
(FilePath -> Command) -> Parser FilePath -> Parser Command
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Mod ArgumentFields FilePath -> Parser FilePath
forall s. IsString s => Mod ArgumentFields s -> Parser s
O.strArgument (FilePath -> Mod ArgumentFields FilePath
forall (f :: * -> *) a. HasMetavar f => FilePath -> Mod f a
O.metavar FilePath
"CABAL.FILE" Mod ArgumentFields FilePath
-> Mod ArgumentFields FilePath -> Mod ArgumentFields FilePath
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod ArgumentFields FilePath
forall (f :: * -> *) a. HasCompleter f => FilePath -> Mod f a
O.action FilePath
"file" 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
O.help FilePath
"Either <pkg.cabal> or cabal.project")
githubP :: Parser Command
githubP = FilePath -> Command
CommandGitHub
(FilePath -> Command) -> Parser FilePath -> Parser Command
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Mod ArgumentFields FilePath -> Parser FilePath
forall s. IsString s => Mod ArgumentFields s -> Parser s
O.strArgument (FilePath -> Mod ArgumentFields FilePath
forall (f :: * -> *) a. HasMetavar f => FilePath -> Mod f a
O.metavar FilePath
"CABAL.FILE" Mod ArgumentFields FilePath
-> Mod ArgumentFields FilePath -> Mod ArgumentFields FilePath
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod ArgumentFields FilePath
forall (f :: * -> *) a. HasCompleter f => FilePath -> Mod f a
O.action FilePath
"file" 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
O.help FilePath
"Either <pkg.cabal> or cabal.project")
parseOptions :: [String] -> IO (FilePath, Options)
parseOptions :: [FilePath] -> IO (FilePath, Options)
parseOptions [FilePath]
argv = case ParserResult (Command, Options)
res of
O.Success (Command
cmd, Options
opts) -> do
FilePath
path <- Command -> IO FilePath
fromCmd Command
cmd
(FilePath, Options) -> IO (FilePath, Options)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (FilePath
path, Options
opts)
O.Failure ParserFailure ParserHelp
f -> case ParserFailure ParserHelp -> FilePath -> (FilePath, ExitCode)
O.renderFailure ParserFailure ParserHelp
f FilePath
"haskell-ci" of
(FilePath
help, ExitCode
_) -> Handle -> FilePath -> IO ()
hPutStrLn Handle
stderr FilePath
help IO () -> IO (FilePath, Options) -> IO (FilePath, Options)
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> IO (FilePath, Options)
forall a. IO a
exitFailure
O.CompletionInvoked CompletionResult
_ -> IO (FilePath, Options)
forall a. IO a
exitFailure
where
res :: ParserResult (Command, Options)
res = ParserPrefs
-> ParserInfo (Command, Options)
-> [FilePath]
-> ParserResult (Command, Options)
forall a.
ParserPrefs -> ParserInfo a -> [FilePath] -> ParserResult a
O.execParserPure (PrefsMod -> ParserPrefs
O.prefs PrefsMod
O.subparserInline) ParserInfo (Command, Options)
cliParserInfo [FilePath]
argv
fromCmd :: Command -> IO FilePath
fromCmd :: Command -> IO FilePath
fromCmd (CommandTravis FilePath
fp) = FilePath -> IO FilePath
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return FilePath
fp
fromCmd (CommandBash FilePath
fp) = FilePath -> IO FilePath
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return FilePath
fp
fromCmd (CommandGitHub FilePath
fp) = FilePath -> IO FilePath
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return FilePath
fp
fromCmd Command
cmd = FilePath -> IO FilePath
forall a. FilePath -> IO a
forall (m :: * -> *) a. MonadFail m => FilePath -> m a
fail (FilePath -> IO FilePath) -> FilePath -> IO FilePath
forall a b. (a -> b) -> a -> b
$ FilePath
"Command without filepath: " FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ Command -> FilePath
forall a. Show a => a -> FilePath
show Command
cmd