[worker] cli: run-all subcommand

parent d78e4177
Pipeline #7036 canceled with stages
{-|
Module : CLI.Types
Description : CLI types
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
-}
{-# LANGUAGE DuplicateRecordFields #-}
module CLI.Types where module CLI.Types where
...@@ -82,6 +95,7 @@ data CLIRoutes ...@@ -82,6 +95,7 @@ data CLIRoutes
data CLIWorker data CLIWorker
= CLIW_run WorkerArgs = CLIW_run WorkerArgs
| CLIW_runAll WorkerAllArgs
| CLIW_stats WorkerStatsArgs | CLIW_stats WorkerStatsArgs
deriving (Show, Eq) deriving (Show, Eq)
...@@ -91,6 +105,10 @@ data WorkerArgs = WorkerArgs ...@@ -91,6 +105,10 @@ data WorkerArgs = WorkerArgs
, worker_run_single :: !Bool , worker_run_single :: !Bool
} deriving (Show, Eq) } deriving (Show, Eq)
data WorkerAllArgs = WorkerAllArgs
{ worker_toml :: !SettingsFile
} deriving (Show, Eq)
data WorkerStatsArgs = WorkerStatsArgs data WorkerStatsArgs = WorkerStatsArgs
{ ws_toml :: !SettingsFile { ws_toml :: !SettingsFile
} deriving (Show, Eq) } deriving (Show, Eq)
......
{-| {-|
Module : Worker.hs Module : CLI.Worker
Description : Gargantext Job Worker Description : Gargantext Job Worker
Copyright : (c) CNRS, 2017-Present Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3 License : AGPL + CECILL v3
...@@ -16,10 +16,12 @@ import Async.Worker.Broker.Types qualified as BT ...@@ -16,10 +16,12 @@ import Async.Worker.Broker.Types qualified as BT
import Async.Worker.Types qualified as W import Async.Worker.Types qualified as W
import CLI.Types import CLI.Types
import CLI.Parsers import CLI.Parsers
import Control.Concurrent.Async (forConcurrently_)
import Data.List qualified as List (cycle, concat, take) import Data.List qualified as List (cycle, concat, take)
import Data.Text qualified as T import Data.Text qualified as T
import Gargantext.Core.Config (hasConfig, gc_worker) import Gargantext.Core.Config (hasConfig, gc_worker)
import Gargantext.Core.Config.Types (SettingsFile(..)) import Gargantext.Core.Config.Types (SettingsFile(..))
import Gargantext.Core.Config.Utils (readConfig)
import Gargantext.Core.Config.Worker (WorkerDefinition(..), WorkerSettings(..), findDefinitionByName) import Gargantext.Core.Config.Worker (WorkerDefinition(..), WorkerSettings(..), findDefinitionByName)
import Gargantext.Core.Worker (withPGMQWorkerCtrlC, withPGMQWorkerSingleCtrlC, initWorkerState) import Gargantext.Core.Worker (withPGMQWorkerCtrlC, withPGMQWorkerSingleCtrlC, initWorkerState)
import Gargantext.Core.Worker.Env (withWorkerEnv) import Gargantext.Core.Worker.Env (withWorkerEnv)
...@@ -65,6 +67,14 @@ workerCLI (CLIW_run (WorkerArgs { .. })) = do ...@@ -65,6 +67,14 @@ workerCLI (CLIW_run (WorkerArgs { .. })) = do
withPGMQWorkerCtrlC env wd $ \a _state -> do withPGMQWorkerCtrlC env wd $ \a _state -> do
-- _ <- runReaderT (sendJob Ping) env -- _ <- runReaderT (sendJob Ping) env
wait a wait a
workerCLI (CLIW_runAll (WorkerAllArgs { .. })) = do
cfg <- readConfig worker_toml
let ws = cfg ^. gc_worker
forConcurrently_ (_wsDefinitions ws) $ \wd -> do
withWorkerEnv worker_toml $ \env -> do
putStrLn $ "Starting worker '" <> _wdName wd <> "' (queue " <> show (_wdQueue wd) <> ")"
withPGMQWorkerCtrlC env wd $ \a _state -> do
wait a
workerCLI (CLIW_stats (WorkerStatsArgs { .. })) = do workerCLI (CLIW_stats (WorkerStatsArgs { .. })) = do
putStrLn ("worker toml: " <> _SettingsFile ws_toml) putStrLn ("worker toml: " <> _SettingsFile ws_toml)
...@@ -95,6 +105,8 @@ workerParser :: Parser CLIWorker ...@@ -95,6 +105,8 @@ workerParser :: Parser CLIWorker
workerParser = hsubparser ( workerParser = hsubparser (
command "run" (info (helper <*> worker_p) command "run" (info (helper <*> worker_p)
(progDesc "Run a single worker")) <> (progDesc "Run a single worker")) <>
command "run-all" (info (helper <*> worker_all_p)
(progDesc "Run all worker definitions")) <>
command "stats" (info (helper <*> stats_p) command "stats" (info (helper <*> stats_p)
(progDesc "Print queue stats")) (progDesc "Print queue stats"))
) )
...@@ -108,6 +120,11 @@ worker_p = fmap CLIW_run $ WorkerArgs ...@@ -108,6 +120,11 @@ worker_p = fmap CLIW_run $ WorkerArgs
<*> flag False True ( long "run-single" <*> flag False True ( long "run-single"
<> help "Whether to loop or run a single job from queue" ) <> help "Whether to loop or run a single job from queue" )
worker_all_p :: Parser CLIWorker
worker_all_p = fmap CLIW_runAll $ WorkerAllArgs
<$> settings_p
stats_p :: Parser CLIWorker stats_p :: Parser CLIWorker
stats_p = fmap CLIW_stats $ WorkerStatsArgs stats_p = fmap CLIW_stats $ WorkerStatsArgs
<$> settings_p <$> settings_p
Markdown is supported
0% or
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment