Commit af381f0a authored by Alfredo Di Napoli's avatar Alfredo Di Napoli

Generalise type of serveJobsAPI

parent 71a30935
{-# LANGUAGE TypeFamilies #-}
module Gargantext.Utils.Jobs ( module Gargantext.Utils.Jobs (
-- * Serving the JOBS API -- * Serving the JOBS API
serveJobsAPI serveJobsAPI
...@@ -7,12 +8,13 @@ module Gargantext.Utils.Jobs ( ...@@ -7,12 +8,13 @@ module Gargantext.Utils.Jobs (
import Control.Monad.Except import Control.Monad.Except
import Control.Monad.Reader import Control.Monad.Reader
import Data.Aeson (ToJSON)
import Data.Monoid (Dual)
import Prelude import Prelude
import System.Directory (doesFileExist) import System.Directory (doesFileExist)
import Text.Read (readMaybe) import Text.Read (readMaybe)
import Gargantext.API.Admin.EnvTypes import Gargantext.API.Admin.EnvTypes
import Gargantext.API.Admin.Orchestrator.Types (JobLog)
import Gargantext.API.Prelude import Gargantext.API.Prelude
import qualified Gargantext.Utils.Jobs.Internal as Internal import qualified Gargantext.Utils.Jobs.Internal as Internal
import Gargantext.Utils.Jobs.Map import Gargantext.Utils.Jobs.Map
...@@ -25,18 +27,22 @@ jobErrorToGargError ...@@ -25,18 +27,22 @@ jobErrorToGargError
jobErrorToGargError = GargJobError jobErrorToGargError = GargJobError
serveJobsAPI serveJobsAPI
:: Foldable callbacks :: (
=> GargJob Foldable callbacks
-> (input -> Logger JobLog -> GargM Env GargError JobLog) , Ord jobType
-> JobsServerAPI ctI ctO callbacks input , Show jobType
serveJobsAPI t f = Internal.serveJobsAPI ask t jobErrorToGargError $ \env i l -> do , ToJSON event
putStrLn ("Running job of type: " ++ show t) , ToJSON result
, MonadJob m jobType (Dual [event]) result
, m ~ (GargM env GargError)
)
=> jobType
-> (input -> Logger event -> m result)
-> SJ.AsyncJobsServerT' ctI ctO callbacks event input result m
serveJobsAPI jobType f = Internal.serveJobsAPI ask jobType jobErrorToGargError $ \env i l -> do
putStrLn ("Running job of type: " ++ show jobType)
runExceptT $ runReaderT (f i l) env runExceptT $ runReaderT (f i l) env
type JobsServerAPI ctI ctO callbacks input =
SJ.AsyncJobsServerT' ctI ctO callbacks JobLog input JobLog
(GargM Env GargError)
parseGargJob :: String -> Maybe GargJob parseGargJob :: String -> Maybe GargJob
parseGargJob s = case s of parseGargJob s = case s of
"tablengrams" -> Just TableNgramsJob "tablengrams" -> Just TableNgramsJob
......
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