module Rollbar.CLI
( Command(..)
, DeployCommand(..)
, parseCommand
, runCommand
) where
import Options.Applicative
import Rollbar.Client
data Command
= CommandPing
| CommandDeploy DeployCommand
deriving (Command -> Command -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Command -> Command -> Bool
$c/= :: Command -> Command -> Bool
== :: Command -> Command -> Bool
$c== :: Command -> Command -> Bool
Eq, Int -> Command -> ShowS
[Command] -> ShowS
Command -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Command] -> ShowS
$cshowList :: [Command] -> ShowS
show :: Command -> String
$cshow :: Command -> String
showsPrec :: Int -> Command -> ShowS
$cshowsPrec :: Int -> Command -> ShowS
Show)
data DeployCommand = DeployCommandReport (Maybe Revision)
deriving (DeployCommand -> DeployCommand -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeployCommand -> DeployCommand -> Bool
$c/= :: DeployCommand -> DeployCommand -> Bool
== :: DeployCommand -> DeployCommand -> Bool
$c== :: DeployCommand -> DeployCommand -> Bool
Eq, Int -> DeployCommand -> ShowS
[DeployCommand] -> ShowS
DeployCommand -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeployCommand] -> ShowS
$cshowList :: [DeployCommand] -> ShowS
show :: DeployCommand -> String
$cshow :: DeployCommand -> String
showsPrec :: Int -> DeployCommand -> ShowS
$cshowsPrec :: Int -> DeployCommand -> ShowS
Show)
parseCommand :: IO Command
parseCommand :: IO Command
parseCommand = forall a. ParserInfo a -> IO a
execParser ParserInfo Command
commandParserInfo
commandParserInfo :: ParserInfo Command
commandParserInfo :: ParserInfo Command
commandParserInfo = forall a. Parser a -> InfoMod a -> ParserInfo a
info (Parser Command
commandParser forall (f :: * -> *) a b. Applicative f => f a -> f (a -> b) -> f b
<**> forall a. Parser (a -> a)
helper) forall a b. (a -> b) -> a -> b
$ forall a. Monoid a => [a] -> a
mconcat
[ forall a. InfoMod a
fullDesc
, forall a. String -> InfoMod a
progDesc String
"Simple CLI to talk with Rollbar API"
]
commandParser :: Parser Command
commandParser :: Parser Command
commandParser = forall a. Mod CommandFields a -> Parser a
subparser forall a b. (a -> b) -> a -> b
$ forall a. Monoid a => [a] -> a
mconcat
[ forall a. String -> ParserInfo a -> Mod CommandFields a
command String
"ping" forall a b. (a -> b) -> a -> b
$ forall a. Parser a -> InfoMod a -> ParserInfo a
info (Parser Command
pingParser forall (f :: * -> *) a b. Applicative f => f a -> f (a -> b) -> f b
<**> forall a. Parser (a -> a)
helper) forall a b. (a -> b) -> a -> b
$ forall a. Monoid a => [a] -> a
mconcat
[ forall a. InfoMod a
fullDesc
, forall a. String -> InfoMod a
progDesc String
"Ping the API server"
]
, forall a. String -> ParserInfo a -> Mod CommandFields a
command String
"deploy" forall a b. (a -> b) -> a -> b
$ forall a. Parser a -> InfoMod a -> ParserInfo a
info (Parser Command
deployParser forall (f :: * -> *) a b. Applicative f => f a -> f (a -> b) -> f b
<**> forall a. Parser (a -> a)
helper) forall a b. (a -> b) -> a -> b
$ forall a. Monoid a => [a] -> a
mconcat
[ forall a. InfoMod a
fullDesc
, forall a. String -> InfoMod a
progDesc String
"Deploy specific commands"
]
]
where
pingParser :: Parser Command
pingParser = forall (f :: * -> *) a. Applicative f => a -> f a
pure Command
CommandPing
deployParser :: Parser Command
deployParser = DeployCommand -> Command
CommandDeploy forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser DeployCommand
deployCommandParser
deployCommandParser :: Parser DeployCommand
deployCommandParser :: Parser DeployCommand
deployCommandParser = forall a. Mod CommandFields a -> Parser a
subparser forall a b. (a -> b) -> a -> b
$
forall a. String -> ParserInfo a -> Mod CommandFields a
command String
"report" forall a b. (a -> b) -> a -> b
$ forall a. Parser a -> InfoMod a -> ParserInfo a
info (Parser DeployCommand
deployCommandReportParser forall (f :: * -> *) a b. Applicative f => f a -> f (a -> b) -> f b
<**> forall a. Parser (a -> a)
helper) forall a b. (a -> b) -> a -> b
$ forall a. Monoid a => [a] -> a
mconcat
[ forall a. InfoMod a
fullDesc
, forall a. String -> InfoMod a
progDesc String
"Tracks a deploy in Rollbar"
]
deployCommandReportParser :: Parser DeployCommand
deployCommandReportParser :: Parser DeployCommand
deployCommandReportParser =
Maybe Revision -> DeployCommand
DeployCommandReport forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (Text -> Revision
Revision forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall s. IsString s => Mod OptionFields s -> Parser s
strOption forall {a}. Mod OptionFields a
revisionOptions)
where
revisionOptions :: Mod OptionFields a
revisionOptions = forall a. Monoid a => [a] -> a
mconcat
[ forall (f :: * -> *) a. HasName f => Char -> Mod f a
short Char
'r'
, forall (f :: * -> *) a. HasName f => String -> Mod f a
long String
"revision"
, forall (f :: * -> *) a. String -> Mod f a
help forall a b. (a -> b) -> a -> b
$ forall a. Monoid a => [a] -> a
mconcat
[ String
"Git SHA of revision being deployed, if this argument is not present"
, String
" it would try to get the value from the configuration file first"
, String
" before calling git."
]
]
runCommand :: Settings -> Command -> IO ()
runCommand :: Settings -> Command -> IO ()
runCommand Settings
settings Command
cmd = do
case Command
cmd of
Command
CommandPing -> do
Pong
pong <- forall (m :: * -> *) a. MonadIO m => Settings -> Rollbar a -> m a
runRollbar Settings
settings forall (m :: * -> *). MonadHttp m => m Pong
ping
forall a. Show a => a -> IO ()
print Pong
pong
CommandDeploy (DeployCommandReport Maybe Revision
mrevision) -> do
DeployId
deployId <- forall (m :: * -> *) a. MonadIO m => Settings -> Rollbar a -> m a
runRollbar Settings
settings forall a b. (a -> b) -> a -> b
$ do
Revision
revision <- case Maybe Revision
mrevision of
Maybe Revision
Nothing -> forall (m :: * -> *). (HasSettings m, MonadIO m) => m Revision
getRevision
Just Revision
revision -> forall (m :: * -> *) a. Monad m => a -> m a
return Revision
revision
Deploy
deploy <- forall (m :: * -> *).
(HasSettings m, MonadIO m) =>
Revision -> m Deploy
mkDeploy Revision
revision
forall (m :: * -> *).
(HasSettings m, MonadHttp m) =>
Deploy -> m DeployId
reportDeploy Deploy
deploy
forall a. Show a => a -> IO ()
print DeployId
deployId