{-# LANGUAGE ApplicativeDo #-}
module DrCabal.Cli
( Command (..)
, readCommand
, WatchArgs (..)
, ProfileArgs (..)
) where
import qualified Options.Applicative as Opt
data Command
= Watch WatchArgs
| Profile ProfileArgs
newtype WatchArgs = WatchArgs
{ WatchArgs -> [Char]
watchArgsOutput :: FilePath
}
newtype ProfileArgs = ProfileArgs
{ ProfileArgs -> [Char]
profileArgsInput :: FilePath
}
readCommand :: IO Command
readCommand :: IO Command
readCommand = forall a. ParserInfo a -> IO a
Opt.execParser ParserInfo Command
opts
where
opts :: ParserInfo Command
opts = forall a. Parser a -> InfoMod a -> ParserInfo a
Opt.info (forall a. Parser (a -> a)
Opt.helper forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Command
commandP) forall a b. (a -> b) -> a -> b
$ forall a. Monoid a => [a] -> a
mconcat
[ forall a. InfoMod a
Opt.fullDesc
, forall a. [Char] -> InfoMod a
Opt.progDesc [Char]
"Profile cabal dependency build output"
, forall a. [Char] -> InfoMod a
Opt.header [Char]
"dr-cabal - a CLI tool to treat cabal output"
]
commandP :: Opt.Parser Command
commandP :: Parser Command
commandP = forall a. Mod CommandFields a -> Parser a
Opt.subparser forall a b. (a -> b) -> a -> b
$ forall a. Monoid a => [a] -> a
mconcat
[ forall a. [Char] -> ParserInfo a -> Mod CommandFields a
Opt.command [Char]
"watch"
forall a b. (a -> b) -> a -> b
$ forall a. Parser a -> InfoMod a -> ParserInfo a
Opt.info (forall a. Parser (a -> a)
Opt.helper forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Command
watchP)
forall a b. (a -> b) -> a -> b
$ forall a. [Char] -> InfoMod a
Opt.progDesc [Char]
"Watch cabal output and save it"
, forall a. [Char] -> ParserInfo a -> Mod CommandFields a
Opt.command [Char]
"profile"
forall a b. (a -> b) -> a -> b
$ forall a. Parser a -> InfoMod a -> ParserInfo a
Opt.info (forall a. Parser (a -> a)
Opt.helper forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Command
profileP)
forall a b. (a -> b) -> a -> b
$ forall a. [Char] -> InfoMod a
Opt.progDesc [Char]
"Output pretty cabal profile results"
]
watchP :: Opt.Parser Command
watchP :: Parser Command
watchP = do
[Char]
watchArgsOutput <- forall s. IsString s => Mod OptionFields s -> Parser s
Opt.strOption forall a b. (a -> b) -> a -> b
$ forall a. Monoid a => [a] -> a
mconcat
[ forall (f :: * -> *) a. HasName f => [Char] -> Mod f a
Opt.long [Char]
"output"
, forall (f :: * -> *) a. HasName f => Char -> Mod f a
Opt.short Char
'o'
, forall (f :: * -> *) a. HasMetavar f => [Char] -> Mod f a
Opt.metavar [Char]
"FILE_PATH"
, forall (f :: * -> *) a. [Char] -> Mod f a
Opt.help [Char]
"Save cabal output to a file in a JSON format"
]
pure $ WatchArgs -> Command
Watch WatchArgs{[Char]
watchArgsOutput :: [Char]
watchArgsOutput :: [Char]
..}
profileP :: Opt.Parser Command
profileP :: Parser Command
profileP = do
[Char]
profileArgsInput <- forall s. IsString s => Mod OptionFields s -> Parser s
Opt.strOption forall a b. (a -> b) -> a -> b
$ forall a. Monoid a => [a] -> a
mconcat
[ forall (f :: * -> *) a. HasName f => [Char] -> Mod f a
Opt.long [Char]
"input"
, forall (f :: * -> *) a. HasName f => Char -> Mod f a
Opt.short Char
'i'
, forall (f :: * -> *) a. HasMetavar f => [Char] -> Mod f a
Opt.metavar [Char]
"FILE_PATH"
, forall (f :: * -> *) a. [Char] -> Mod f a
Opt.help [Char]
"Read profile input from a JSON file, created by 'dr-cabal watch'"
]
pure $ ProfileArgs -> Command
Profile ProfileArgs{[Char]
profileArgsInput :: [Char]
profileArgsInput :: [Char]
..}