1 {-# OPTIONS_GHC -fno-warn-unused-top-binds #-}
3 Module : Gargantext.API.Ngrams
4 Description : Server API
5 Copyright : (c) CNRS, 2017-Present
6 License : AGPL + CECILL v3
7 Maintainer : team@gargantext.org
8 Stability : experimental
14 get ngrams filtered by NgramsType
19 {-# LANGUAGE ConstraintKinds #-}
20 {-# LANGUAGE ScopedTypeVariables #-}
21 {-# LANGUAGE TemplateHaskell #-}
22 {-# LANGUAGE TypeOperators #-}
23 {-# LANGUAGE TypeFamilies #-}
25 module Gargantext.API.Ngrams
32 --, rmListNgrams TODO fix before exporting
33 , apiNgramsTableCorpus
56 , NgramsRepoElement(..)
82 , listNgramsChangedSince
86 import Control.Concurrent
87 import Control.Lens ((.~), view, (^.), (^..), (+~), (%~), (.~), sumOf, at, _Just, Each(..), (%%~), mapped)
88 import Control.Monad.Reader
89 import Data.Aeson hiding ((.=))
90 import qualified Data.Aeson.Text as DAT
91 import Data.Either (Either(..))
93 import qualified Data.List as List
94 import Data.Map.Strict (Map)
95 import qualified Data.Map.Strict as Map
96 import qualified Data.Map.Strict.Patch as PM
97 import Data.Maybe (fromMaybe)
99 import Data.Ord (Down(..))
100 import Data.Patch.Class (Action(act), Transformable(..), ours)
101 import qualified Data.Set as S
102 import qualified Data.Set as Set
103 import Data.Swagger hiding (version, patch)
104 import Data.Text (Text, isInfixOf, unpack)
105 import Data.Text.Lazy.IO as DTL
106 import Formatting (hprint, int, (%))
107 import Formatting.Clock (timeSpecs)
108 import GHC.Generics (Generic)
109 import Servant hiding (Patch)
110 import System.Clock (getTime, TimeSpec, Clock(..))
111 import Servant.Job.Async (JobFunction(..), serveJobsAPI)
112 import System.IO (stderr)
113 import Test.QuickCheck (elements)
114 import Test.QuickCheck.Arbitrary (Arbitrary, arbitrary)
116 import Prelude (error)
117 import Gargantext.Prelude
119 import Gargantext.API.Admin.Orchestrator.Types (JobLog(..), AsyncJobs)
120 import Gargantext.API.Admin.Types (HasSettings)
121 import qualified Gargantext.API.Metrics as Metrics
122 import Gargantext.API.Ngrams.Types
123 import Gargantext.API.Prelude
124 import Gargantext.Core.Types (ListType(..), NodeId, ListId, DocId, Limit, Offset, TODO, assertValid)
125 import Gargantext.Core.Utils (something)
126 -- import Gargantext.Core.Viz.Graph.API (recomputeGraph)
127 -- import Gargantext.Core.Viz.Graph.Distances (Distance(Conditional))
128 import Gargantext.Database.Action.Flow.Types
129 import Gargantext.Database.Action.Metrics.NgramsByNode (getOccByNgramsOnlyFast')
130 import Gargantext.Database.Admin.Config (userMaster)
131 import Gargantext.Database.Admin.Types.Node (NodeType(..))
132 import Gargantext.Database.Prelude (HasConnectionPool, HasConfig)
133 import Gargantext.Database.Query.Table.Node.Select
134 import Gargantext.Database.Query.Table.Ngrams hiding (NgramsType(..), ngrams, ngramsType, ngrams_terms)
135 import Gargantext.Database.Query.Table.Node.Error (HasNodeError)
136 import qualified Gargantext.Database.Query.Table.Ngrams as TableNgrams
137 import Gargantext.Database.Query.Table.Node (getNode)
138 import Gargantext.Database.Schema.Node (node_id, node_parentId, node_userId)
139 import Gargantext.Prelude.Job
142 -- TODO sequences of modifications (Patchs)
143 type NgramsIdPatch = Patch NgramsId NgramsPatch
145 ngramsPatch :: Int -> NgramsPatch
146 ngramsPatch n = NgramsPatch (DM.fromList [(1, StopTerm)]) (Set.fromList [n]) Set.empty
148 toEdit :: NgramsId -> NgramsPatch -> Edit NgramsId NgramsPatch
149 toEdit n p = Edit n p
150 ngramsIdPatch :: Patch NgramsId NgramsPatch
151 ngramsIdPatch = fromList $ catMaybes $ reverse [ replace (1::NgramsId) (Just $ ngramsPatch 1) Nothing
152 , replace (1::NgramsId) Nothing (Just $ ngramsPatch 2)
153 , replace (2::NgramsId) Nothing (Just $ ngramsPatch 2)
156 -- applyPatchBack :: Patch -> IO Patch
157 -- isEmptyPatch = Map.all (\x -> Set.isEmpty (add_children x) && Set.isEmpty ... )
159 ------------------------------------------------------------------------
160 ------------------------------------------------------------------------
161 ------------------------------------------------------------------------
164 -- TODO: Replace.old is ignored which means that if the current list
165 -- `MapTerm` and that the patch is `Replace CandidateTerm StopTerm` then
166 -- the list is going to be `StopTerm` while it should keep `MapTerm`.
167 -- However this should not happen in non conflicting situations.
168 mkListsUpdate :: NgramsType -> NgramsTablePatch -> [(NgramsTypeId, NgramsTerm, ListTypeId)]
169 mkListsUpdate nt patches =
170 [ (ngramsTypeId nt, ng, listTypeId lt)
171 | (ng, patch) <- patches ^.. ntp_ngrams_patches . ifolded . withIndex
172 , lt <- patch ^.. patch_list . new
175 mkChildrenGroups :: (PatchSet NgramsTerm -> Set NgramsTerm)
178 -> [(NgramsTypeId, NgramsParent, NgramsChild)]
179 mkChildrenGroups addOrRem nt patches =
180 [ (ngramsTypeId nt, parent, child)
181 | (parent, patch) <- patches ^.. ntp_ngrams_patches . ifolded . withIndex
182 , child <- patch ^.. patch_children . to addOrRem . folded
186 ------------------------------------------------------------------------
188 saveRepo :: ( MonadReader env m, MonadBase IO m, HasRepoSaver env )
190 saveRepo = liftBase =<< view repoSaver
192 listTypeConflictResolution :: ListType -> ListType -> ListType
193 listTypeConflictResolution _ _ = undefined -- TODO Use Map User ListType
195 ngramsStatePatchConflictResolution
196 :: TableNgrams.NgramsType
199 -> ConflictResolutionNgramsPatch
200 ngramsStatePatchConflictResolution _ngramsType _nodeId _ngramsTerm
201 = (ours, (const ours, ours), (False, False))
202 -- (False, False) mean here that Mod has always priority.
203 -- (True, False) <- would mean priority to the left (same as ours).
205 -- undefined {- TODO think this through -}, listTypeConflictResolution)
208 -- Insertions are not considered as patches,
209 -- they do not extend history,
210 -- they do not bump version.
211 insertNewOnly :: a -> Maybe b -> a
212 insertNewOnly m = maybe m (const $ error "insertNewOnly: impossible")
213 -- TODO error handling
216 -- TODO refactor with putListNgrams
217 copyListNgrams :: RepoCmdM env err m
218 => NodeId -> NodeId -> NgramsType
220 copyListNgrams srcListId dstListId ngramsType = do
222 liftBase $ modifyMVar_ var $
223 pure . (r_state . at ngramsType %~ (Just . f . something))
226 f :: Map NodeId NgramsTableMap -> Map NodeId NgramsTableMap
227 f m = m & at dstListId %~ insertNewOnly (m ^. at srcListId)
229 -- TODO refactor with putListNgrams
230 -- The list must be non-empty!
231 -- The added ngrams must be non-existent!
232 addListNgrams :: RepoCmdM env err m
233 => NodeId -> NgramsType
234 -> [NgramsElement] -> m ()
235 addListNgrams listId ngramsType nes = do
237 liftBase $ modifyMVar_ var $
238 pure . (r_state . at ngramsType . _Just . at listId . _Just <>~ m)
241 m = Map.fromList $ (\n -> (n ^. ne_ngrams, n)) <$> nes
245 rmListNgrams :: RepoCmdM env err m
247 -> TableNgrams.NgramsType
249 rmListNgrams l nt = setListNgrams l nt mempty
251 -- | TODO: incr the Version number
252 -- && should use patch
254 setListNgrams :: RepoCmdM env err m
256 -> TableNgrams.NgramsType
257 -> Map NgramsTerm NgramsRepoElement
259 setListNgrams listId ngramsType ns = do
261 liftBase $ modifyMVar_ var $
265 (at listId .~ ( Just ns))
272 currentVersion :: RepoCmdM env err m
276 r <- liftBase $ readMVar var
277 pure $ r ^. r_version
280 -- tableNgramsPut :: (HasInvalidError err, RepoCmdM env err m)
281 commitStatePatch :: RepoCmdM env err m => Versioned NgramsStatePatch -> m (Versioned NgramsStatePatch)
282 commitStatePatch (Versioned p_version p) = do
284 vq' <- liftBase $ modifyMVar var $ \r -> do
286 q = mconcat $ take (r ^. r_version - p_version) (r ^. r_history)
287 (p', q') = transformWith ngramsStatePatchConflictResolution p q
288 r' = r & r_version +~ 1
290 & r_history %~ (p' :)
292 -- Ideally we would like to check these properties. However:
293 -- * They should be checked only to debug the code. The client data
294 -- should be able to trigger these.
295 -- * What kind of error should they throw (we are in IO here)?
296 -- * Should we keep modifyMVar?
297 -- * Should we throw the validation in an Exception, catch it around
298 -- modifyMVar and throw it back as an Error?
299 assertValid $ transformable p q
300 assertValid $ applicable p' (r ^. r_state)
302 pure (r', Versioned (r' ^. r_version) q')
307 -- This is a special case of tableNgramsPut where the input patch is empty.
308 tableNgramsPull :: RepoCmdM env err m
310 -> TableNgrams.NgramsType
312 -> m (Versioned NgramsTablePatch)
313 tableNgramsPull listId ngramsType p_version = do
315 r <- liftBase $ readMVar var
318 q = mconcat $ take (r ^. r_version - p_version) (r ^. r_history)
319 q_table = q ^. _PatchMap . at ngramsType . _Just . _PatchMap . at listId . _Just
321 pure (Versioned (r ^. r_version) q_table)
323 -- Apply the given patch to the DB and returns the patch to be applied on the
326 tableNgramsPut :: ( FlowCmdM env err m
331 -> Versioned NgramsTablePatch
332 -> m (Versioned NgramsTablePatch)
333 tableNgramsPut tabType listId (Versioned p_version p_table)
334 | p_table == mempty = do
335 let ngramsType = ngramsTypeFromTabType tabType
336 tableNgramsPull listId ngramsType p_version
339 let ngramsType = ngramsTypeFromTabType tabType
340 (p0, p0_validity) = PM.singleton listId p_table
341 (p, p_validity) = PM.singleton ngramsType p0
343 assertValid p0_validity
344 assertValid p_validity
346 ret <- commitStatePatch (Versioned p_version p)
347 <&> v_data %~ (view (_PatchMap . at ngramsType . _Just . _PatchMap . at listId . _Just))
352 tableNgramsPostChartsAsync :: ( FlowCmdM env err m
355 => UpdateTableNgramsCharts
358 tableNgramsPostChartsAsync utn logStatus = do
359 let tabType = utn ^. utn_tab_type
360 let listId = utn ^. utn_list_id
362 node <- getNode listId
363 let nId = node ^. node_id
364 _uId = node ^. node_userId
365 mCId = node ^. node_parentId
367 printDebug "[tableNgramsPut] tabType" tabType
368 printDebug "[tableNgramsPut] listId" listId
372 printDebug "[tableNgramsPut] can't update charts, no parent, nId" nId
373 pure $ jobLogFail $ jobLogInit 1
377 -- printDebug "[tableNgramsPut] Authors, updating Pie, cId" cId
378 (logRef, logRefSuccess, getRef) <- runJobLog 1 logStatus
380 _ <- Metrics.updatePie cId (Just listId) tabType Nothing
385 -- printDebug "[tableNgramsPut] Institutes, updating Tree, cId" cId
386 -- printDebug "[tableNgramsPut] updating tree StopTerm, cId" cId
387 (logRef, logRefSuccess, getRef) <- runJobLog 3 logStatus
389 _ <- Metrics.updateTree cId (Just listId) tabType StopTerm
390 -- printDebug "[tableNgramsPut] updating tree CandidateTerm, cId" cId
392 _ <- Metrics.updateTree cId (Just listId) tabType CandidateTerm
393 -- printDebug "[tableNgramsPut] updating tree MapTerm, cId" cId
395 _ <- Metrics.updateTree cId (Just listId) tabType MapTerm
400 -- printDebug "[tableNgramsPut] Sources, updating chart, cId" cId
401 (logRef, logRefSuccess, getRef) <- runJobLog 1 logStatus
403 _ <- Metrics.updatePie cId (Just listId) tabType Nothing
408 -- printDebug "[tableNgramsPut] Terms, updating Metrics (Histo), cId" cId
409 (logRef, logRefSuccess, getRef) <- runJobLog 6 logStatus
411 _ <- Metrics.updateChart cId (Just listId) tabType Nothing
413 _ <- Metrics.updatePie cId (Just listId) tabType Nothing
415 _ <- Metrics.updateScatter cId (Just listId) tabType Nothing
417 _ <- Metrics.updateTree cId (Just listId) tabType StopTerm
419 _ <- Metrics.updateTree cId (Just listId) tabType CandidateTerm
421 _ <- Metrics.updateTree cId (Just listId) tabType MapTerm
426 printDebug "[tableNgramsPut] no update for tabType = " tabType
427 pure $ jobLogFail $ jobLogInit 1
430 { _ne_list :: ListType
431 If we merge the parents/children we can potentially create cycles!
432 , _ne_parent :: Maybe NgramsTerm
433 , _ne_children :: MSet NgramsTerm
437 getNgramsTableMap :: RepoCmdM env err m
439 -> TableNgrams.NgramsType
440 -> m (Versioned NgramsTableMap)
441 getNgramsTableMap nodeId ngramsType = do
443 repo <- liftBase $ readMVar v
444 pure $ Versioned (repo ^. r_version)
445 (repo ^. r_state . at ngramsType . _Just . at nodeId . _Just)
447 dumpJsonTableMap :: RepoCmdM env err m
450 -> TableNgrams.NgramsType
452 dumpJsonTableMap fpath nodeId ngramsType = do
453 m <- getNgramsTableMap nodeId ngramsType
454 liftBase $ DTL.writeFile (unpack fpath) (DAT.encodeToLazyText m)
460 -- | TODO Errors management
461 -- TODO: polymorphic for Annuaire or Corpus or ...
462 -- | Table of Ngrams is a ListNgrams formatted (sorted and/or cut).
463 -- TODO: should take only one ListId
465 getTime' :: MonadBase IO m => m TimeSpec
466 getTime' = liftBase $ getTime ProcessCPUTime
469 getTableNgrams :: forall env err m.
470 (RepoCmdM env err m, HasNodeError err, HasConnectionPool env, HasConfig env)
471 => NodeType -> NodeId -> TabType
472 -> ListId -> Limit -> Maybe Offset
474 -> Maybe MinSize -> Maybe MaxSize
476 -> (NgramsTerm -> Bool)
477 -> m (Versioned NgramsTable)
478 getTableNgrams _nType nId tabType listId limit_ offset
479 listType minSize maxSize orderBy searchQuery = do
482 -- lIds <- selectNodesWithUsername NodeList userMaster
484 ngramsType = ngramsTypeFromTabType tabType
485 offset' = maybe 0 identity offset
486 listType' = maybe (const True) (==) listType
487 minSize' = maybe (const True) (<=) minSize
488 maxSize' = maybe (const True) (>=) maxSize
490 selected_node n = minSize' s
492 && searchQuery (n ^. ne_ngrams)
493 && listType' (n ^. ne_list)
497 selected_inner roots n = maybe False (`Set.member` roots) (n ^. ne_root)
499 ---------------------------------------
500 sortOnOrder Nothing = identity
501 sortOnOrder (Just TermAsc) = List.sortOn $ view ne_ngrams
502 sortOnOrder (Just TermDesc) = List.sortOn $ Down . view ne_ngrams
503 sortOnOrder (Just ScoreAsc) = List.sortOn $ view ne_occurrences
504 sortOnOrder (Just ScoreDesc) = List.sortOn $ Down . view ne_occurrences
506 ---------------------------------------
507 selectAndPaginate :: Map NgramsTerm NgramsElement -> [NgramsElement]
508 selectAndPaginate tableMap = roots <> inners
510 list = tableMap ^.. each
511 rootOf ne = maybe ne (\r -> fromMaybe (panic "getTableNgrams: invalid root") (tableMap ^. at r))
513 selected_nodes = list & take limit_
515 . filter selected_node
516 . sortOnOrder orderBy
517 roots = rootOf <$> selected_nodes
518 rootsSet = Set.fromList (_ne_ngrams <$> roots)
519 inners = list & filter (selected_inner rootsSet)
521 ---------------------------------------
522 setScores :: forall t. Each t t NgramsElement NgramsElement => Bool -> t -> m t
523 setScores False table = pure table
524 setScores True table = do
525 let ngrams_terms = unNgramsTerm <$> (table ^.. each . ne_ngrams)
527 occurrences <- getOccByNgramsOnlyFast' nId
532 liftBase $ hprint stderr
533 ("getTableNgrams/setScores #ngrams=" % int % " time=" % timeSpecs % "\n")
534 (length ngrams_terms) t1 t2
536 occurrences <- getOccByNgramsOnlySlow nType nId
542 setOcc ne = ne & ne_occurrences .~ sumOf (at (unNgramsTerm (ne ^. ne_ngrams)) . _Just) occurrences
544 pure $ table & each %~ setOcc
545 ---------------------------------------
547 -- lists <- catMaybes <$> listsWith userMaster
548 -- trace (show lists) $
549 -- getNgramsTableMap ({-lists <>-} listIds) ngramsType
551 let scoresNeeded = needsScores orderBy
552 tableMap1 <- getNgramsTableMap listId ngramsType
554 tableMap2 <- tableMap1 & v_data %%~ setScores scoresNeeded
555 . Map.mapWithKey ngramsElementFromRepo
557 tableMap3 <- tableMap2 & v_data %%~ fmap NgramsTable
558 . setScores (not scoresNeeded)
561 liftBase $ hprint stderr
562 ("getTableNgrams total=" % timeSpecs
563 % " map1=" % timeSpecs
564 % " map2=" % timeSpecs
565 % " map3=" % timeSpecs
566 % " sql=" % (if scoresNeeded then "map2" else "map3")
568 ) t0 t3 t0 t1 t1 t2 t2 t3
572 scoresRecomputeTableNgrams :: forall env err m. (RepoCmdM env err m, HasNodeError err, HasConnectionPool env, HasConfig env) => NodeId -> TabType -> ListId -> m Int
573 scoresRecomputeTableNgrams nId tabType listId = do
574 tableMap <- getNgramsTableMap listId ngramsType
575 _ <- tableMap & v_data %%~ setScores
576 . Map.mapWithKey ngramsElementFromRepo
580 ngramsType = ngramsTypeFromTabType tabType
582 setScores :: forall t. Each t t NgramsElement NgramsElement => t -> m t
584 let ngrams_terms = unNgramsTerm <$> (table ^.. each . ne_ngrams)
585 occurrences <- getOccByNgramsOnlyFast' nId
590 setOcc ne = ne & ne_occurrences .~ sumOf (at (unNgramsTerm (ne ^. ne_ngrams)) . _Just) occurrences
592 pure $ table & each %~ setOcc
598 -- TODO: find a better place for the code above, All APIs stay here
600 data OrderBy = TermAsc | TermDesc | ScoreAsc | ScoreDesc
601 deriving (Generic, Enum, Bounded, Read, Show)
603 instance FromHttpApiData OrderBy
605 parseUrlPiece "TermAsc" = pure TermAsc
606 parseUrlPiece "TermDesc" = pure TermDesc
607 parseUrlPiece "ScoreAsc" = pure ScoreAsc
608 parseUrlPiece "ScoreDesc" = pure ScoreDesc
609 parseUrlPiece _ = Left "Unexpected value of OrderBy"
612 instance ToParamSchema OrderBy
613 instance FromJSON OrderBy
614 instance ToJSON OrderBy
615 instance ToSchema OrderBy
616 instance Arbitrary OrderBy
618 arbitrary = elements [minBound..maxBound]
620 needsScores :: Maybe OrderBy -> Bool
621 needsScores (Just ScoreAsc) = True
622 needsScores (Just ScoreDesc) = True
623 needsScores _ = False
625 type TableNgramsApiGet = Summary " Table Ngrams API Get"
626 :> QueryParamR "ngramsType" TabType
627 :> QueryParamR "list" ListId
628 :> QueryParamR "limit" Limit
629 :> QueryParam "offset" Offset
630 :> QueryParam "listType" ListType
631 :> QueryParam "minTermSize" MinSize
632 :> QueryParam "maxTermSize" MaxSize
633 :> QueryParam "orderBy" OrderBy
634 :> QueryParam "search" Text
635 :> Get '[JSON] (Versioned NgramsTable)
637 type TableNgramsApiPut = Summary " Table Ngrams API Change"
638 :> QueryParamR "ngramsType" TabType
639 :> QueryParamR "list" ListId
640 :> ReqBody '[JSON] (Versioned NgramsTablePatch)
641 :> Put '[JSON] (Versioned NgramsTablePatch)
643 type RecomputeScoresNgramsApiGet = Summary " Recompute scores for ngrams table"
644 :> QueryParamR "ngramsType" TabType
645 :> QueryParamR "list" ListId
646 :> "recompute" :> Post '[JSON] Int
648 type TableNgramsApiGetVersion = Summary " Table Ngrams API Get Version"
649 :> QueryParamR "ngramsType" TabType
650 :> QueryParamR "list" ListId
651 :> Get '[JSON] Version
653 type TableNgramsApi = TableNgramsApiGet
654 :<|> TableNgramsApiPut
655 :<|> RecomputeScoresNgramsApiGet
656 :<|> "version" :> TableNgramsApiGetVersion
657 :<|> TableNgramsAsyncApi
659 type TableNgramsAsyncApi = Summary "Table Ngrams Async API"
663 :> AsyncJobs JobLog '[JSON] UpdateTableNgramsCharts JobLog
665 getTableNgramsCorpus :: (RepoCmdM env err m, HasNodeError err, HasConnectionPool env, HasConfig env)
672 -> Maybe MinSize -> Maybe MaxSize
674 -> Maybe Text -- full text search
675 -> m (Versioned NgramsTable)
676 getTableNgramsCorpus nId tabType listId limit_ offset listType minSize maxSize orderBy mt =
677 getTableNgrams NodeCorpus nId tabType listId limit_ offset listType minSize maxSize orderBy searchQuery
679 searchQuery (NgramsTerm nt) = maybe (const True) isInfixOf mt nt
681 getTableNgramsVersion :: (RepoCmdM env err m, HasNodeError err, HasConnectionPool env, HasConfig env)
686 getTableNgramsVersion _nId _tabType _listId = currentVersion
688 -- Versioned { _v_version = v } <- getTableNgramsCorpus nId tabType listId 100000 Nothing Nothing Nothing Nothing Nothing Nothing
689 -- This line above looks like a waste of computation to finally get only the version.
690 -- See the comment about listNgramsChangedSince.
693 -- | Text search is deactivated for now for ngrams by doc only
694 getTableNgramsDoc :: (RepoCmdM env err m, HasNodeError err, HasConnectionPool env, HasConfig env)
696 -> ListId -> Limit -> Maybe Offset
698 -> Maybe MinSize -> Maybe MaxSize
700 -> Maybe Text -- full text search
701 -> m (Versioned NgramsTable)
702 getTableNgramsDoc dId tabType listId limit_ offset listType minSize maxSize orderBy _mt = do
703 ns <- selectNodesWithUsername NodeList userMaster
704 let ngramsType = ngramsTypeFromTabType tabType
705 ngs <- selectNgramsByDoc (ns <> [listId]) dId ngramsType
706 let searchQuery (NgramsTerm nt) = flip S.member (S.fromList ngs) nt
707 getTableNgrams NodeDocument dId tabType listId limit_ offset listType minSize maxSize orderBy searchQuery
711 apiNgramsTableCorpus :: ( GargServerC env err m
713 => NodeId -> ServerT TableNgramsApi m
714 apiNgramsTableCorpus cId = getTableNgramsCorpus cId
716 :<|> scoresRecomputeTableNgrams cId
717 :<|> getTableNgramsVersion cId
718 :<|> apiNgramsAsync cId
720 apiNgramsTableDoc :: ( GargServerC env err m
722 => DocId -> ServerT TableNgramsApi m
723 apiNgramsTableDoc dId = getTableNgramsDoc dId
725 :<|> scoresRecomputeTableNgrams dId
726 :<|> getTableNgramsVersion dId
727 :<|> apiNgramsAsync dId
728 -- > index all the corpus accordingly (TODO AD)
730 apiNgramsAsync :: NodeId -> GargServer TableNgramsAsyncApi
731 apiNgramsAsync _dId =
733 JobFunction $ \i log ->
736 printDebug "tableNgramsPostChartsAsync" x
738 in tableNgramsPostChartsAsync i log'
740 -- Did the given list of ngrams changed since the given version?
741 -- The returned value is versioned boolean value, meaning that one always retrieve the
743 -- If the given version is negative then one simply receive the latest version and True.
744 -- Using this function is more precise than simply comparing the latest version number
745 -- with the local version number. Indeed there might be no change to this particular list
746 -- and still the version number has changed because of other lists.
748 -- Here the added value is to make a compromise between precision, computation, and bandwidth:
749 -- * currentVersion: good computation, good bandwidth, bad precision.
750 -- * listNgramsChangedSince: good precision, good bandwidth, bad computation.
751 -- * tableNgramsPull: good precision, good bandwidth (if you use the received data!), bad computation.
752 listNgramsChangedSince :: RepoCmdM env err m
753 => ListId -> TableNgrams.NgramsType -> Version -> m (Versioned Bool)
754 listNgramsChangedSince listId ngramsType version
756 Versioned <$> currentVersion <*> pure True
758 tableNgramsPull listId ngramsType version & mapped . v_data %~ (== mempty)