1 {-# LANGUAGE MultiWayIf, FunctionalDependencies, MultiParamTypeClasses #-}
2 module Gargantext.Utils.Jobs.Monad where
4 import Gargantext.Utils.Jobs.Settings
5 import Gargantext.Utils.Jobs.Map
6 import Gargantext.Utils.Jobs.Queue
7 import Gargantext.Utils.Jobs.State
9 import Control.Concurrent.STM
10 import Control.Exception
11 import Control.Monad.Except
13 import Data.Time.Clock
14 import Network.HTTP.Client (Manager)
17 import qualified Servant.Job.Core as SJ
18 import qualified Servant.Job.Types as SJ
20 data JobEnv t w a = JobEnv
21 { jeSettings :: JobSettings
22 , jeState :: JobsState t w a
23 , jeManager :: Manager
27 :: (EnumBounded t, Monoid w)
32 newJobEnv js prios mgr = JobEnv js <$> newJobsState js prios <*> pure mgr
36 defaultJobSettings :: NumRunners -> SJ.SecretKey -> JobSettings
37 defaultJobSettings numRunners k = JobSettings
38 { jsNumRunners = numRunners
39 , jsJobTimeout = 30 * 60 -- 30 minutes
40 , jsIDTimeout = 30 * 60 -- 30 minutes
41 , jsGcPeriod = 1 * 60 -- 1 minute
45 genSecret :: IO SJ.SecretKey
46 genSecret = SJ.generateSecretKey
48 class MonadIO m => MonadJob m t w a | m -> t w a where
49 getJobEnv :: m (JobEnv t w a)
51 getJobsSettings :: MonadJob m t w a => m JobSettings
52 getJobsSettings = jeSettings <$> getJobEnv
54 getJobsState :: MonadJob m t w a => m (JobsState t w a)
55 getJobsState = jeState <$> getJobEnv
57 getJobsMap :: MonadJob m t w a => m (JobMap (SJ.JobID 'SJ.Safe) w a)
58 getJobsMap = jobsData <$> getJobsState
60 getJobsQueue :: MonadJob m t w a => m (Queue t (SJ.JobID 'SJ.Safe))
61 getJobsQueue = jobsQ <$> getJobsState
64 :: (MonadJob m t w a, Ord t)
67 -> (i -> Logger w -> IO a)
68 -> m (SJ.JobID 'SJ.Safe)
69 queueJob jobkind input f = do
72 liftIO (pushJob jobkind input f js st)
77 -> m (Maybe (JobEntry (SJ.JobID 'SJ.Safe) w a))
80 liftIO $ lookupJob jid jmap
87 | JobException SomeException
92 => SJ.JobID 'SJ.Unsafe
93 -> m (Either JobError (SJ.JobID 'SJ.Safe))
94 checkJID (SJ.PrivateID tn n t d) = do
95 now <- liftIO getCurrentTime
97 if | tn /= "job" -> return (Left InvalidIDType)
98 | now > addUTCTime (fromIntegral $ jsIDTimeout js) t -> return (Left IDExpired)
99 | d /= SJ.macID tn (jsSecretKey js) t n -> return (Left InvalidMacID)
100 | otherwise -> return $ Right (SJ.PrivateID tn n t d)
104 => SJ.JobID 'SJ.Unsafe
105 -> (SJ.JobID 'SJ.Safe -> JobEntry (SJ.JobID 'SJ.Safe) w a -> m r)
106 -> m (Either JobError (Maybe r))
110 Left e -> return (Left e)
114 Nothing -> return (Right Nothing)
115 Just j -> Right . Just <$> f jid' j
120 -> m (Either JobError a)
122 handleIDError toE act = act >>= \r -> case r of
123 Left err -> throwError (toE err)
127 :: (Ord t, MonadJob m t w a)
128 => Bool -- is it queued (and we have to remove jid from queue)
132 removeJob queued t jid = do
135 liftIO . atomically $ do