{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE PartialTypeSignatures #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE DataKinds #-}
module OddJobs.Cli where
import Options.Applicative as Opts
import Data.Text
import OddJobs.Job (startJobRunner, Config(..))
import System.Daemonize (DaemonOptions(..), daemonize)
import System.FilePath (FilePath)
import System.Posix.Process (getProcessID)
import qualified System.Directory as Dir
import qualified System.Exit as Exit
import System.Environment (getProgName)
import OddJobs.Types (Seconds(..), delaySeconds)
import qualified System.Posix.Signals as Sig
import qualified UnliftIO.Async as Async
import qualified OddJobs.Endpoints as UI
import Servant.Server as Servant
import Servant.API
import Data.Proxy
import Data.Text.Encoding (decodeUtf8)
import Network.Wai.Handler.Warp as Warp
import Debug.Trace
defaultMain :: ((Config -> IO ()) -> IO ())
-> IO ()
defaultMain startFn = do
Args{argsCommand} <- customExecParser defaultCliParserPrefs defaultCliInfo
case argsCommand of
Start cmdArgs -> do
defaultStartCommand cmdArgs startFn
Stop cmdArgs -> do
defaultStopCommand cmdArgs
Status ->
Prelude.error "not implemented yet"
defaultStartCommand :: StartArgs
-> ((Config -> IO ()) -> IO ())
-> IO ()
defaultStartCommand args@StartArgs{..} startFn = do
progName <- getProgName
case startDaemonize of
False -> do
startFn coreStartupFn
True -> do
(Dir.doesPathExist startPidFile) >>= \case
True -> do
putStrLn $
"PID file already exists. Please check if " <> progName <> " is still running in the background." <>
" If not, you can safely delete this file and start " <> progName <> " again: " <> startPidFile
Exit.exitWith (Exit.ExitFailure 1)
False -> do
daemonize defaultDaemonOptions (pure ()) $ const $ do
pid <- getProcessID
writeFile startPidFile (show pid)
putStrLn $ "Started " <> progName <> " in background with PID=" <> show pid <> ". PID written to " <> startPidFile
startFn $ \cfg -> coreStartupFn cfg{cfgPidFile = Just startPidFile}
where
coreStartupFn cfg = do
Async.withAsync (defaultWebUi args cfg) $ \_ -> do
startJobRunner cfg
defaultWebUi :: StartArgs
-> Config
-> IO ()
defaultWebUi StartArgs{..} cfg@Config{..} = do
env <- UI.mkEnv cfg ("/" <>)
case startWebUiAuth of
Nothing -> pure ()
Just AuthNone ->
let app = UI.server cfg env Prelude.id
in Warp.run startWebUiPort $
Servant.serve (Proxy :: Proxy UI.FinalAPI) app
Just (AuthBasic u p) ->
let api = Proxy :: Proxy (BasicAuth "OddJobs Admin UI" OddJobsUser :> UI.FinalAPI)
ctx = defaultBasicAuth (u, p) :. EmptyContext
app _ = UI.server cfg env Prelude.id
in Warp.run startWebUiPort $
Servant.serveWithContext api ctx app
defaultStopCommand :: StopArgs
-> IO ()
defaultStopCommand StopArgs{..} = do
progName <- getProgName
pid <- read <$> (readFile shutPidFile)
if (shutTimeout == Seconds 0)
then forceKill pid
else do putStrLn $ "Sending SIGINT to pid=" <> show pid <>
" and waiting " <> (show $ unSeconds shutTimeout) <> " seconds for graceful stop"
Sig.signalProcess Sig.sigINT pid
(Async.race (delaySeconds shutTimeout) checkProcessStatus) >>= \case
Right _ -> do
putStrLn $ progName <> " seems to have exited gracefully."
Exit.exitSuccess
Left _ -> do
putStrLn $ progName <> " has still not exited."
forceKill pid
where
forceKill pid = do
putStrLn $ "Sending SIGKILL to pid=" <> show pid
Sig.signalProcess Sig.sigKILL pid
checkProcessStatus = do
Dir.doesPathExist shutPidFile >>= \case
True -> do
delaySeconds (Seconds 1)
checkProcessStatus
False -> do
pure ()
data Args = Args
{ argsCommand :: !Command
} deriving (Eq, Show)
argParser :: Parser Args
argParser = Args <$> commandParser
data Command
= Start StartArgs
| Stop StopArgs
| Status
deriving (Eq, Show)
commandParser :: Parser Command
commandParser = hsubparser
( command "start" (info startParser (progDesc "start the odd-jobs runner")) <>
command "stop" (info stopParser (progDesc "stop the odd-jobs runner")) <>
command "status" (info statusParser (progDesc "print status of all active jobs"))
)
data StartArgs = StartArgs
{
startWebUiAuth :: !(Maybe WebUiAuth)
, startWebUiPort :: !Int
, startDaemonize :: !Bool
, startPidFile :: !FilePath
} deriving (Eq, Show)
startParser :: Parser Command
startParser = fmap Start $ StartArgs
<$> webUiAuthParser
<*> option auto ( long "web-ui-port" <>
metavar "PORT" <>
value 7777 <>
showDefault <>
help "The port on which the Web UI listens. Please note, to actually enable the Web UI you need to pick one of the available auth schemes"
)
<*> switch ( long "daemonize" <>
help "Fork the job-runner as a background daemon. If omitted, the job-runner remains in the foreground."
)
<*> pidFileParser
data WebUiAuth
= AuthNone
| AuthBasic !Text !Text
deriving (Eq, Show)
webUiAuthParser :: Parser (Maybe WebUiAuth)
webUiAuthParser = basicAuthParser <|> noAuthParser <|> (pure Nothing)
where
basicAuthParser = fmap Just $ AuthBasic
<$> strOption ( long "web-ui-basic-auth-user" <>
metavar "USER" <>
help "Username for basic auth"
)
<*> strOption ( long "web-ui-basic-auth-password" <>
metavar "PASS" <>
help "Password for basic auth"
)
noAuthParser = flag' (Just AuthNone)
( long "web-ui-no-auth" <>
help "Start the web UI with any authentication. NOT RECOMMENDED."
)
data StopArgs = StopArgs
{
shutTimeout :: !Seconds
, shutPidFile :: !FilePath
} deriving (Eq, Show)
stopParser :: Parser Command
stopParser = fmap Stop $ StopArgs
<$> option (Seconds <$> auto) ( long "timeout" <>
metavar "TIMEOUT" <>
help "Maximum seconds to wait before force-killing the background daemon."
)
<*> pidFileParser
statusParser :: Parser Command
statusParser = pure Status
pidFileParser :: Parser FilePath
pidFileParser =
strOption ( long "pid-file" <>
metavar "PIDFILE" <>
value "./odd-jobs.pid" <>
showDefault <>
help "Path of the PID file for the daemon. Takes effect only during stop or only when using the --daemonize option at startup"
)
defaultCliParserPrefs :: ParserPrefs
defaultCliParserPrefs = prefs $
showHelpOnError <>
showHelpOnEmpty
defaultCliInfo :: ParserInfo Args
defaultCliInfo =
info (argParser <**> helper) fullDesc
defaultDaemonOptions :: DaemonOptions
defaultDaemonOptions = DaemonOptions
{ daemonShouldChangeDirectory = False
, daemonShouldCloseStandardStreams = False
, daemonShouldIgnoreSignals = True
, daemonUserToChangeTo = Nothing
, daemonGroupToChangeTo = Nothing
}
data OddJobsUser = OddJobsUser !Text !Text deriving (Eq, Show)
defaultBasicAuth :: (Text, Text) -> BasicAuthCheck OddJobsUser
defaultBasicAuth (user, pass) = BasicAuthCheck $ \b ->
let u = decodeUtf8 (basicAuthUsername b)
p = decodeUtf8 (basicAuthPassword b)
in if u==user && p==pass
then pure (Authorized $ OddJobsUser u p)
else pure BadPassword