Commit 922bb0b8 authored by Przemyslaw Kaminski's avatar Przemyslaw Kaminski

[ngrams] async endpoint for ngrams put

This updates charts as well
parent 3b7f4b9f
Pipeline #1171 failed with stage
{-# OPTIONS_GHC -fno-warn-unused-top-binds #-}
{-# OPTIONS_GHC -fno-warn-unused-top-binds -fno-warn-name-shadowing #-}
{-|
Module : Gargantext.API.Ngrams
Description : Server API
......@@ -108,6 +108,7 @@ import Formatting.Clock (timeSpecs)
import GHC.Generics (Generic)
import Servant hiding (Patch)
import System.Clock (getTime, TimeSpec, Clock(..))
import Servant.Job.Async (JobFunction(..), serveJobsAPI)
import System.IO (stderr)
import Test.QuickCheck (elements)
import Test.QuickCheck.Arbitrary (Arbitrary, arbitrary)
......@@ -115,24 +116,27 @@ import Test.QuickCheck.Arbitrary (Arbitrary, arbitrary)
import Prelude (error)
import Gargantext.Prelude
import Gargantext.API.Admin.Orchestrator.Types (JobLog(..), AsyncJobs)
import Gargantext.API.Admin.Types (HasSettings)
import qualified Gargantext.API.Metrics as Metrics
import Gargantext.API.Ngrams.Types
import Gargantext.Core.Types (ListType(..), NodeId, ListId, DocId, Limit, Offset, HasInvalidError, TODO, assertValid)
import Gargantext.API.Prelude
import Gargantext.Core.Types (ListType(..), NodeId, ListId, DocId, Limit, Offset, TODO, assertValid)
import Gargantext.Core.Utils (something)
-- import Gargantext.Core.Viz.Graph.API (recomputeGraph)
-- import Gargantext.Core.Viz.Graph.Distances (Distance(Conditional))
import Gargantext.Database.Action.Flow.Types
import Gargantext.Database.Action.Metrics.NgramsByNode (getOccByNgramsOnlyFast')
import Gargantext.Database.Query.Table.Node.Select
import Gargantext.Database.Query.Table.Ngrams hiding (NgramsType(..), ngrams, ngramsType, ngrams_terms)
import Gargantext.Database.Admin.Config (userMaster)
import Gargantext.Database.Query.Table.Node.Error (HasNodeError)
import Gargantext.Database.Admin.Types.Node (NodeType(..))
import Gargantext.Database.Prelude (HasConnectionPool, HasConfig)
import Gargantext.Database.Query.Table.Node.Select
import Gargantext.Database.Query.Table.Ngrams hiding (NgramsType(..), ngrams, ngramsType, ngrams_terms)
import Gargantext.Database.Query.Table.Node.Error (HasNodeError)
import qualified Gargantext.Database.Query.Table.Ngrams as TableNgrams
import Gargantext.Database.Query.Table.Node (getNode)
import Gargantext.Database.Query.Tree.Error (HasTreeError)
import Gargantext.Database.Schema.Node (node_id, node_parentId, node_userId)
import Gargantext.Prelude.Job
{-
-- TODO sequences of modifications (Patchs)
......@@ -319,13 +323,8 @@ tableNgramsPull listId ngramsType p_version = do
-- Apply the given patch to the DB and returns the patch to be applied on the
-- client.
-- TODO-ACCESS check
tableNgramsPut :: ( HasNodeError err
, HasTreeError err
, HasInvalidError err
, HasConfig env
, HasConnectionPool env
tableNgramsPut :: ( FlowCmdM env err m
, HasSettings env
, RepoCmdM env err m
)
=> TabType
-> ListId
......@@ -347,55 +346,86 @@ tableNgramsPut tabType listId (Versioned p_version p_table)
ret <- commitStatePatch (Versioned p_version p)
<&> v_data %~ (view (_PatchMap . at ngramsType . _Just . _PatchMap . at listId . _Just))
pure ret
tableNgramsPutAsync :: ( FlowCmdM env err m
, HasSettings env
)
=> UpdateTableNgrams
-> (JobLog -> m ())
-> m JobLog
tableNgramsPutAsync utn logStatus = do
-- let (Versioned p_version p_table) = utn ^. utn_patch
let tabType = utn ^. utn_tab_type
let listId = utn ^. utn_list_id
node <- getNode listId
let nId = node ^. node_id
_uId = node ^. node_userId
mCId = node ^. node_parentId
-- printDebug "[tableNgramsPut] updating graph with nId" nId
-- printDebug "[tableNgramsPut] updating graph with uId" uId
-- _ <- recomputeGraph uId nId Conditional
printDebug "[tableNgramsPut] tabType" tabType
printDebug "[tableNgramsPut] listId" listId
_ <- case mCId of
case mCId of
Nothing -> do
printDebug "[tableNgramsPut] can't update charts, no parent, nId" nId
pure ()
pure $ jobLogFail $ jobLogInit 1
Just cId -> do
case tabType of
Authors -> do
-- printDebug "[tableNgramsPut] Authors, updating Pie, cId" cId
let jl = jobLogInit 1
logStatus jl
_ <- Metrics.updatePie cId (Just listId) tabType Nothing
pure ()
pure $ jobLogSuccess jl
Institutes -> do
-- printDebug "[tableNgramsPut] Institutes, updating Tree, cId" cId
-- printDebug "[tableNgramsPut] updating tree StopTerm, cId" cId
let jl = jobLogInit 3
logStatus jl
_ <- Metrics.updateTree cId (Just listId) tabType StopTerm
-- printDebug "[tableNgramsPut] updating tree CandidateTerm, cId" cId
let jl = jobLogSuccess jl
logStatus jl
_ <- Metrics.updateTree cId (Just listId) tabType CandidateTerm
-- printDebug "[tableNgramsPut] updating tree MapTerm, cId" cId
let jl = jobLogSuccess jl
logStatus jl
_ <- Metrics.updateTree cId (Just listId) tabType MapTerm
pure ()
pure $ jobLogSuccess jl
Sources -> do
-- printDebug "[tableNgramsPut] Sources, updating chart, cId" cId
let jl = jobLogInit 1
logStatus jl
_ <- Metrics.updatePie cId (Just listId) tabType Nothing
pure ()
pure $ jobLogSuccess jl
Terms -> do
-- printDebug "[tableNgramsPut] Terms, updating Metrics (Histo), cId" cId
let jl = jobLogInit 6
logStatus jl
_ <- Metrics.updateChart cId (Just listId) tabType Nothing
let jl = jobLogSuccess jl
logStatus jl
_ <- Metrics.updatePie cId (Just listId) tabType Nothing
let jl = jobLogSuccess jl
logStatus jl
_ <- Metrics.updateScatter cId (Just listId) tabType Nothing
let jl = jobLogSuccess jl
logStatus jl
_ <- Metrics.updateTree cId (Just listId) tabType StopTerm
let jl = jobLogSuccess jl
logStatus jl
_ <- Metrics.updateTree cId (Just listId) tabType CandidateTerm
let jl = jobLogSuccess jl
logStatus jl
_ <- Metrics.updateTree cId (Just listId) tabType MapTerm
pure ()
pure $ jobLogSuccess jl
_ -> do
printDebug "[tableNgramsPut] no update for tabType = " tabType
pure ()
pure ()
pure ret
pure $ jobLogFail $ jobLogInit 1
{-
{ _ne_list :: ListType
If we merge the parents/children we can potentially create cycles!
......@@ -624,6 +654,12 @@ type TableNgramsApi = TableNgramsApiGet
:<|> TableNgramsApiPut
:<|> RecomputeScoresNgramsApiGet
:<|> "version" :> TableNgramsApiGetVersion
:<|> TableNgramsAsyncApi
type TableNgramsAsyncApi = Summary "Table Ngrams Async API"
:> "async"
:> "update"
:> AsyncJobs JobLog '[JSON] UpdateTableNgrams JobLog
getTableNgramsCorpus :: (RepoCmdM env err m, HasNodeError err, HasConnectionPool env, HasConfig env)
=> NodeId
......@@ -671,35 +707,35 @@ getTableNgramsDoc dId tabType listId limit_ offset listType minSize maxSize orde
apiNgramsTableCorpus :: ( RepoCmdM env err m
, HasNodeError err
, HasTreeError err
, HasInvalidError err
, HasConnectionPool env
, HasConfig env
, HasSettings env
apiNgramsTableCorpus :: ( GargServerC env err m
)
=> NodeId -> ServerT TableNgramsApi m
apiNgramsTableCorpus cId = getTableNgramsCorpus cId
:<|> tableNgramsPut
:<|> scoresRecomputeTableNgrams cId
:<|> getTableNgramsVersion cId
:<|> apiNgramsAsync cId
apiNgramsTableDoc :: ( RepoCmdM env err m
, HasNodeError err
, HasTreeError err
, HasInvalidError err
, HasConnectionPool env
, HasConfig env
, HasSettings env
apiNgramsTableDoc :: ( GargServerC env err m
)
=> DocId -> ServerT TableNgramsApi m
apiNgramsTableDoc dId = getTableNgramsDoc dId
:<|> tableNgramsPut
:<|> scoresRecomputeTableNgrams dId
:<|> getTableNgramsVersion dId
:<|> apiNgramsAsync dId
-- > index all the corpus accordingly (TODO AD)
apiNgramsAsync :: NodeId -> GargServer TableNgramsAsyncApi
apiNgramsAsync _dId =
serveJobsAPI $
JobFunction (\i l ->
let
log' x = do
printDebug "tableNgramsPutAsync" x
liftBase $ l x
in tableNgramsPutAsync i log')
-- Did the given list of ngrams changed since the given version?
-- The returned value is versioned boolean value, meaning that one always retrieve the
-- latest version.
......
......@@ -38,6 +38,7 @@ import Data.Validity
import Database.PostgreSQL.Simple.FromField (FromField, fromField, ResultError(ConversionFailed), returnError)
import GHC.Generics (Generic)
import Servant hiding (Patch)
import Servant.Job.Utils (jsonOptions)
import System.FileLock (FileLock)
import Test.QuickCheck (elements, frequency)
import Test.QuickCheck.Arbitrary (Arbitrary, arbitrary)
......@@ -46,7 +47,7 @@ import Protolude (maybeToEither)
import Gargantext.Prelude
import Gargantext.Core.Text (size)
import Gargantext.Core.Types (ListType(..), NodeId)
import Gargantext.Core.Types (ListType(..), ListId, NodeId)
import Gargantext.Core.Types (TODO)
import Gargantext.Core.Utils.Prefix (unPrefix, unPrefixUntagged, unPrefixSwagger, wellNamedSchema)
import Gargantext.Database.Prelude (fromField', CmdM')
......@@ -735,3 +736,18 @@ ngramsTypeFromTabType tabType =
Terms -> TableNgrams.NgramsTerms
_ -> panic $ lieu <> "No Ngrams for this tab"
-- TODO: This `panic` would disapear with custom NgramsType.
----
-- PUT Async task
data UpdateTableNgrams = UpdateTableNgrams
{ _utn_tab_type :: !TabType
, _utn_list_id :: !ListId
, _utn_patch :: !(Versioned NgramsTablePatch)
} deriving (Eq, Show, Generic)
makeLenses ''UpdateTableNgrams
instance FromJSON UpdateTableNgrams where
parseJSON = genericParseJSON $ jsonOptions "_utn_"
instance ToSchema UpdateTableNgrams where
declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "_utn_")
......@@ -120,7 +120,8 @@ type GargPrivateAPI' =
-- Document endpoint
:<|> "document" :> Summary "Document endpoint"
:> Capture "doc_id" DocId
:> "ngrams" :> TableNgramsApi
:> "ngrams"
:> TableNgramsApi
-- :<|> "counts" :> Stream GET NewLineFraming '[JSON] Count :> CountAPI
-- TODO-SECURITY
......
module Gargantext.Prelude.Job where
import Data.Maybe
import Gargantext.Prelude
import Gargantext.API.Admin.Orchestrator.Types (JobLog(..))
jobLogInit :: Int -> JobLog
jobLogInit rem =
JobLog { _scst_succeeded = Just 0
, _scst_remaining = Just rem
, _scst_failed = Just 0
, _scst_events = Just [] }
jobLogSuccess :: JobLog -> JobLog
jobLogSuccess (JobLog { _scst_succeeded = mSucc
, _scst_remaining = mRem
, _scst_failed = mFail
, _scst_events = evt }) =
JobLog { _scst_succeeded = (+ 1) <$> mSucc
, _scst_remaining = (+ 1) <$> mRem
, _scst_failed = mFail
, _scst_events = evt }
jobLogFail :: JobLog -> JobLog
jobLogFail (JobLog { _scst_succeeded = mSucc
, _scst_remaining = mRem
, _scst_failed = mFail
, _scst_events = evt }) =
JobLog { _scst_succeeded = (+ 1) <$> mSucc
, _scst_remaining = (\x -> x - 1) <$> mRem
, _scst_failed = (+ 1) <$> mFail
, _scst_events = evt }
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