2 Module : Gargantext.API.Ngrams
3 Description : Server API
4 Copyright : (c) CNRS, 2017-Present
5 License : AGPL + CECILL v3
6 Maintainer : team@gargantext.org
7 Stability : experimental
13 get ngrams filtered by NgramsType
18 {-# OPTIONS_GHC -fno-warn-unused-top-binds #-}
20 {-# LANGUAGE ConstraintKinds #-}
21 {-# LANGUAGE ScopedTypeVariables #-}
22 {-# LANGUAGE TypeOperators #-}
23 {-# LANGUAGE TypeFamilies #-}
25 module Gargantext.API.Ngrams
32 --, rmListNgrams TODO fix before exporting
33 , apiNgramsTableCorpus
56 , NgramsRepoElement(..)
81 , VersionedWithCount(..)
83 , listNgramsChangedSince
87 import Control.Concurrent
88 import Control.Lens ((.~), view, (^.), (^..), (+~), (%~), (.~), sumOf, at, _Just, Each(..), (%%~), mapped, ifolded, withIndex)
89 import Control.Monad.Reader
90 import Data.Aeson hiding ((.=))
91 import Data.Either (Either(..))
93 import Data.Map.Strict (Map)
94 import Data.Maybe (fromMaybe)
96 import Data.Ord (Down(..))
97 import Data.Patch.Class (Action(act), Transformable(..), ours)
98 import Data.Swagger hiding (version, patch)
99 import Data.Text (Text, isInfixOf, unpack)
100 import Data.Text.Lazy.IO as DTL
101 import Formatting (hprint, int, (%))
102 import GHC.Generics (Generic)
103 import Gargantext.API.Admin.Orchestrator.Types (JobLog(..), AsyncJobs)
104 import Gargantext.API.Admin.Types (HasSettings)
105 import Gargantext.API.Ngrams.Types
106 import Gargantext.API.Prelude
107 import Gargantext.Core.Types (ListType(..), NodeId, ListId, DocId, Limit, Offset, TODO, assertValid)
108 import Gargantext.Core.Utils (something)
109 import Gargantext.Database.Action.Flow.Types
110 import Gargantext.Database.Action.Metrics.NgramsByNode (getOccByNgramsOnlyFast')
111 import Gargantext.Database.Admin.Config (userMaster)
112 import Gargantext.Database.Admin.Types.Node (NodeType(..))
113 import Gargantext.Database.Prelude (HasConnectionPool, HasConfig)
114 import Gargantext.Database.Query.Table.Ngrams hiding (NgramsType(..), ngramsType, ngrams_terms)
115 import Gargantext.Database.Query.Table.Node (getNode)
116 import Gargantext.Database.Query.Table.Node.Error (HasNodeError)
117 import Gargantext.Database.Query.Table.Node.Select
118 import Gargantext.Database.Schema.Node (node_id, node_parentId, node_userId)
119 import Gargantext.Prelude hiding (log)
120 import Gargantext.Prelude.Job
121 import Gargantext.Prelude.Utils (hasTime, getTime)
122 import Prelude (error)
123 import Servant hiding (Patch)
124 import Servant.Job.Async (JobFunction(..), serveJobsAPI)
125 import System.IO (stderr)
126 import Test.QuickCheck (elements)
127 import Test.QuickCheck.Arbitrary (Arbitrary, arbitrary)
128 import qualified Data.Aeson.Text as DAT
129 import qualified Data.List as List
130 import qualified Data.Map.Strict as Map
131 import qualified Data.Map.Strict.Patch as PM
132 import qualified Data.Set as S
133 import qualified Data.Set as Set
134 import qualified Gargantext.API.Metrics as Metrics
135 import qualified Gargantext.Database.Query.Table.Ngrams as TableNgrams
138 -- TODO sequences of modifications (Patchs)
139 type NgramsIdPatch = Patch NgramsId NgramsPatch
141 ngramsPatch :: Int -> NgramsPatch
142 ngramsPatch n = NgramsPatch (DM.fromList [(1, StopTerm)]) (Set.fromList [n]) Set.empty
144 toEdit :: NgramsId -> NgramsPatch -> Edit NgramsId NgramsPatch
145 toEdit n p = Edit n p
146 ngramsIdPatch :: Patch NgramsId NgramsPatch
147 ngramsIdPatch = fromList $ catMaybes $ reverse [ replace (1::NgramsId) (Just $ ngramsPatch 1) Nothing
148 , replace (1::NgramsId) Nothing (Just $ ngramsPatch 2)
149 , replace (2::NgramsId) Nothing (Just $ ngramsPatch 2)
152 -- applyPatchBack :: Patch -> IO Patch
153 -- isEmptyPatch = Map.all (\x -> Set.isEmpty (add_children x) && Set.isEmpty ... )
155 ------------------------------------------------------------------------
156 ------------------------------------------------------------------------
157 ------------------------------------------------------------------------
160 -- TODO: Replace.old is ignored which means that if the current list
161 -- `MapTerm` and that the patch is `Replace CandidateTerm StopTerm` then
162 -- the list is going to be `StopTerm` while it should keep `MapTerm`.
163 -- However this should not happen in non conflicting situations.
164 mkListsUpdate :: NgramsType -> NgramsTablePatch -> [(NgramsTypeId, NgramsTerm, ListTypeId)]
165 mkListsUpdate nt patches =
166 [ (ngramsTypeId nt, ng, listTypeId lt)
167 | (ng, patch) <- patches ^.. ntp_ngrams_patches . ifolded . withIndex
168 , lt <- patch ^.. patch_list . new
171 mkChildrenGroups :: (PatchSet NgramsTerm -> Set NgramsTerm)
174 -> [(NgramsTypeId, NgramsParent, NgramsChild)]
175 mkChildrenGroups addOrRem nt patches =
176 [ (ngramsTypeId nt, parent, child)
177 | (parent, patch) <- patches ^.. ntp_ngrams_patches . ifolded . withIndex
178 , child <- patch ^.. patch_children . to addOrRem . folded
182 ------------------------------------------------------------------------
184 saveRepo :: ( MonadReader env m, MonadBase IO m, HasRepoSaver env )
186 saveRepo = liftBase =<< view repoSaver
188 listTypeConflictResolution :: ListType -> ListType -> ListType
189 listTypeConflictResolution _ _ = undefined -- TODO Use Map User ListType
191 ngramsStatePatchConflictResolution
192 :: TableNgrams.NgramsType
195 -> ConflictResolutionNgramsPatch
196 ngramsStatePatchConflictResolution _ngramsType _nodeId _ngramsTerm
197 = (ours, (const ours, ours), (False, False))
198 -- (False, False) mean here that Mod has always priority.
199 -- (True, False) <- would mean priority to the left (same as ours).
201 -- undefined {- TODO think this through -}, listTypeConflictResolution)
204 -- Insertions are not considered as patches,
205 -- they do not extend history,
206 -- they do not bump version.
207 insertNewOnly :: a -> Maybe b -> a
208 insertNewOnly m = maybe m (const $ error "insertNewOnly: impossible")
209 -- TODO error handling
212 -- TODO refactor with putListNgrams
213 copyListNgrams :: RepoCmdM env err m
214 => NodeId -> NodeId -> NgramsType
216 copyListNgrams srcListId dstListId ngramsType = do
218 liftBase $ modifyMVar_ var $
219 pure . (r_state . at ngramsType %~ (Just . f . something))
222 f :: Map NodeId NgramsTableMap -> Map NodeId NgramsTableMap
223 f m = m & at dstListId %~ insertNewOnly (m ^. at srcListId)
225 -- TODO refactor with putListNgrams
226 -- The list must be non-empty!
227 -- The added ngrams must be non-existent!
228 addListNgrams :: RepoCmdM env err m
229 => NodeId -> NgramsType
230 -> [NgramsElement] -> m ()
231 addListNgrams listId ngramsType nes = do
233 liftBase $ modifyMVar_ var $
234 pure . (r_state . at ngramsType . _Just . at listId . _Just <>~ m)
237 m = Map.fromList $ (\n -> (n ^. ne_ngrams, n)) <$> nes
241 rmListNgrams :: RepoCmdM env err m
243 -> TableNgrams.NgramsType
245 rmListNgrams l nt = setListNgrams l nt mempty
247 -- | TODO: incr the Version number
248 -- && should use patch
250 setListNgrams :: RepoCmdM env err m
252 -> TableNgrams.NgramsType
253 -> Map NgramsTerm NgramsRepoElement
255 setListNgrams listId ngramsType ns = do
257 liftBase $ modifyMVar_ var $
261 (at listId .~ ( Just ns))
268 currentVersion :: RepoCmdM env err m
272 r <- liftBase $ readMVar var
273 pure $ r ^. r_version
275 newNgramsFromNgramsStatePatch :: NgramsStatePatch -> [Ngrams]
276 newNgramsFromNgramsStatePatch p =
277 [ text2ngrams (unNgramsTerm n)
278 | (n,np) <- p ^.. _PatchMap . each . _PatchMap . each . _NgramsTablePatch . _PatchMap . ifolded . withIndex
279 , _ <- np ^.. patch_new . _Just
282 -- tableNgramsPut :: (HasInvalidError err, RepoCmdM env err m)
283 commitStatePatch :: RepoCmdM env err m => Versioned NgramsStatePatch -> m (Versioned NgramsStatePatch)
284 commitStatePatch (Versioned p_version p) = do
286 vq' <- liftBase $ modifyMVar var $ \r -> do
288 q = mconcat $ take (r ^. r_version - p_version) (r ^. r_history)
289 (p', q') = transformWith ngramsStatePatchConflictResolution p q
290 r' = r & r_version +~ 1
292 & r_history %~ (p' :)
294 -- Ideally we would like to check these properties. However:
295 -- * They should be checked only to debug the code. The client data
296 -- should be able to trigger these.
297 -- * What kind of error should they throw (we are in IO here)?
298 -- * Should we keep modifyMVar?
299 -- * Should we throw the validation in an Exception, catch it around
300 -- modifyMVar and throw it back as an Error?
301 assertValid $ transformable p q
302 assertValid $ applicable p' (r ^. r_state)
304 pure (r', Versioned (r' ^. r_version) q')
309 _ <- insertNgrams (newNgramsFromNgramsStatePatch p)
313 -- This is a special case of tableNgramsPut where the input patch is empty.
314 tableNgramsPull :: RepoCmdM env err m
316 -> TableNgrams.NgramsType
318 -> m (Versioned NgramsTablePatch)
319 tableNgramsPull listId ngramsType p_version = do
321 r <- liftBase $ readMVar var
324 q = mconcat $ take (r ^. r_version - p_version) (r ^. r_history)
325 q_table = q ^. _PatchMap . at ngramsType . _Just . _PatchMap . at listId . _Just
327 pure (Versioned (r ^. r_version) q_table)
329 -- Apply the given patch to the DB and returns the patch to be applied on the
332 tableNgramsPut :: ( FlowCmdM env err m
337 -> Versioned NgramsTablePatch
338 -> m (Versioned NgramsTablePatch)
339 tableNgramsPut tabType listId (Versioned p_version p_table)
340 | p_table == mempty = do
341 let ngramsType = ngramsTypeFromTabType tabType
342 tableNgramsPull listId ngramsType p_version
345 let ngramsType = ngramsTypeFromTabType tabType
346 (p0, p0_validity) = PM.singleton listId p_table
347 (p, p_validity) = PM.singleton ngramsType p0
349 assertValid p0_validity
350 assertValid p_validity
352 ret <- commitStatePatch (Versioned p_version p)
353 <&> v_data %~ (view (_PatchMap . at ngramsType . _Just . _PatchMap . at listId . _Just))
358 tableNgramsPostChartsAsync :: ( FlowCmdM env err m
362 => UpdateTableNgramsCharts
365 tableNgramsPostChartsAsync utn logStatus = do
366 let tabType = utn ^. utn_tab_type
367 let listId = utn ^. utn_list_id
369 node <- getNode listId
370 let nId = node ^. node_id
371 _uId = node ^. node_userId
372 mCId = node ^. node_parentId
374 printDebug "[tableNgramsPut] tabType" tabType
375 printDebug "[tableNgramsPut] listId" listId
379 printDebug "[tableNgramsPut] can't update charts, no parent, nId" nId
380 pure $ jobLogFail $ jobLogInit 1
384 -- printDebug "[tableNgramsPut] Authors, updating Pie, cId" cId
385 (logRef, logRefSuccess, getRef) <- runJobLog 1 logStatus
387 _ <- Metrics.updatePie cId (Just listId) tabType Nothing
392 -- printDebug "[tableNgramsPut] Institutes, updating Tree, cId" cId
393 -- printDebug "[tableNgramsPut] updating tree StopTerm, cId" cId
394 (logRef, logRefSuccess, getRef) <- runJobLog 3 logStatus
396 _ <- Metrics.updateTree cId (Just listId) tabType StopTerm
397 -- printDebug "[tableNgramsPut] updating tree CandidateTerm, cId" cId
399 _ <- Metrics.updateTree cId (Just listId) tabType CandidateTerm
400 -- printDebug "[tableNgramsPut] updating tree MapTerm, cId" cId
402 _ <- Metrics.updateTree cId (Just listId) tabType MapTerm
407 -- printDebug "[tableNgramsPut] Sources, updating chart, cId" cId
408 (logRef, logRefSuccess, getRef) <- runJobLog 1 logStatus
410 _ <- Metrics.updatePie cId (Just listId) tabType Nothing
415 -- printDebug "[tableNgramsPut] Terms, updating Metrics (Histo), cId" cId
416 (logRef, logRefSuccess, getRef) <- runJobLog 6 logStatus
419 _ <- Metrics.updateChart cId (Just listId) tabType Nothing
421 _ <- Metrics.updatePie cId (Just listId) tabType Nothing
423 _ <- Metrics.updateScatter cId (Just listId) tabType Nothing
425 _ <- Metrics.updateTree cId (Just listId) tabType StopTerm
427 _ <- Metrics.updateTree cId (Just listId) tabType CandidateTerm
429 _ <- Metrics.updateTree cId (Just listId) tabType MapTerm
435 printDebug "[tableNgramsPut] no update for tabType = " tabType
436 pure $ jobLogFail $ jobLogInit 1
439 { _ne_list :: ListType
440 If we merge the parents/children we can potentially create cycles!
441 , _ne_parent :: Maybe NgramsTerm
442 , _ne_children :: MSet NgramsTerm
446 getNgramsTableMap :: RepoCmdM env err m
448 -> TableNgrams.NgramsType
449 -> m (Versioned NgramsTableMap)
450 getNgramsTableMap nodeId ngramsType = do
452 repo <- liftBase $ readMVar v
453 pure $ Versioned (repo ^. r_version)
454 (repo ^. r_state . at ngramsType . _Just . at nodeId . _Just)
456 dumpJsonTableMap :: RepoCmdM env err m
459 -> TableNgrams.NgramsType
461 dumpJsonTableMap fpath nodeId ngramsType = do
462 m <- getNgramsTableMap nodeId ngramsType
463 liftBase $ DTL.writeFile (unpack fpath) (DAT.encodeToLazyText m)
469 -- | TODO Errors management
470 -- TODO: polymorphic for Annuaire or Corpus or ...
471 -- | Table of Ngrams is a ListNgrams formatted (sorted and/or cut).
472 -- TODO: should take only one ListId
475 getTableNgrams :: forall env err m.
476 (RepoCmdM env err m, HasNodeError err, HasConnectionPool env, HasConfig env)
477 => NodeType -> NodeId -> TabType
478 -> ListId -> Limit -> Maybe Offset
480 -> Maybe MinSize -> Maybe MaxSize
482 -> (NgramsTerm -> Bool)
483 -> m (VersionedWithCount NgramsTable)
484 getTableNgrams _nType nId tabType listId limit_ offset
485 listType minSize maxSize orderBy searchQuery = do
488 -- lIds <- selectNodesWithUsername NodeList userMaster
490 ngramsType = ngramsTypeFromTabType tabType
491 offset' = maybe 0 identity offset
492 listType' = maybe (const True) (==) listType
493 minSize' = maybe (const True) (<=) minSize
494 maxSize' = maybe (const True) (>=) maxSize
496 selected_node n = minSize' s
498 && searchQuery (n ^. ne_ngrams)
499 && listType' (n ^. ne_list)
503 selected_inner roots n = maybe False (`Set.member` roots) (n ^. ne_root)
505 ---------------------------------------
506 sortOnOrder Nothing = identity
507 sortOnOrder (Just TermAsc) = List.sortOn $ view ne_ngrams
508 sortOnOrder (Just TermDesc) = List.sortOn $ Down . view ne_ngrams
509 sortOnOrder (Just ScoreAsc) = List.sortOn $ view ne_occurrences
510 sortOnOrder (Just ScoreDesc) = List.sortOn $ Down . view ne_occurrences
512 ---------------------------------------
514 filteredNodes :: Map NgramsTerm NgramsElement -> [NgramsElement]
515 filteredNodes tableMap = rootOf <$> list & filter selected_node
517 rootOf ne = maybe ne (\r -> fromMaybe (panic "getTableNgrams: invalid root") (tableMap ^. at r))
519 list = tableMap ^.. each
521 ---------------------------------------
522 selectAndPaginate :: Map NgramsTerm NgramsElement -> [NgramsElement]
523 selectAndPaginate tableMap = roots <> inners
525 list = tableMap ^.. each
526 rootOf ne = maybe ne (\r -> fromMaybe (panic "getTableNgrams: invalid root") (tableMap ^. at r))
528 selected_nodes = list & take limit_
530 . filter selected_node
531 . sortOnOrder orderBy
532 roots = rootOf <$> selected_nodes
533 rootsSet = Set.fromList (_ne_ngrams <$> roots)
534 inners = list & filter (selected_inner rootsSet)
536 ---------------------------------------
537 setScores :: forall t. Each t t NgramsElement NgramsElement => Bool -> t -> m t
538 setScores False table = pure table
539 setScores True table = do
540 let ngrams_terms = table ^.. each . ne_ngrams
542 occurrences <- getOccByNgramsOnlyFast' nId
547 liftBase $ hprint stderr
548 ("getTableNgrams/setScores #ngrams=" % int % " time=" % hasTime % "\n")
549 (length ngrams_terms) t1 t2
551 occurrences <- getOccByNgramsOnlySlow nType nId
557 setOcc ne = ne & ne_occurrences .~ sumOf (at (ne ^. ne_ngrams) . _Just) occurrences
559 pure $ table & each %~ setOcc
560 ---------------------------------------
562 -- lists <- catMaybes <$> listsWith userMaster
563 -- trace (show lists) $
564 -- getNgramsTableMap ({-lists <>-} listIds) ngramsType
567 let scoresNeeded = needsScores orderBy
568 tableMap1 <- getNgramsTableMap listId ngramsType
570 tableMap2 <- tableMap1 & v_data %%~ setScores scoresNeeded
571 . Map.mapWithKey ngramsElementFromRepo
573 fltr <- tableMap2 & v_data %%~ fmap NgramsTable . setScores (not scoresNeeded)
575 let fltrCount = length $ fltr ^. v_data . _NgramsTable
578 tableMap3 <- tableMap2 & v_data %%~ fmap NgramsTable
579 . setScores (not scoresNeeded)
582 liftBase $ hprint stderr
583 ("getTableNgrams total=" % hasTime
587 % " sql=" % (if scoresNeeded then "map2" else "map3")
589 ) t0 t3 t0 t1 t1 t2 t2 t3
590 pure $ toVersionedWithCount fltrCount tableMap3
593 scoresRecomputeTableNgrams :: forall env err m. (RepoCmdM env err m, HasNodeError err, HasConnectionPool env, HasConfig env) => NodeId -> TabType -> ListId -> m Int
594 scoresRecomputeTableNgrams nId tabType listId = do
595 tableMap <- getNgramsTableMap listId ngramsType
596 _ <- tableMap & v_data %%~ setScores
597 . Map.mapWithKey ngramsElementFromRepo
601 ngramsType = ngramsTypeFromTabType tabType
603 setScores :: forall t. Each t t NgramsElement NgramsElement => t -> m t
605 let ngrams_terms = table ^.. each . ne_ngrams
606 occurrences <- getOccByNgramsOnlyFast' nId
611 setOcc ne = ne & ne_occurrences .~ sumOf (at (ne ^. ne_ngrams) . _Just) occurrences
613 pure $ table & each %~ setOcc
619 -- TODO: find a better place for the code above, All APIs stay here
621 data OrderBy = TermAsc | TermDesc | ScoreAsc | ScoreDesc
622 deriving (Generic, Enum, Bounded, Read, Show)
624 instance FromHttpApiData OrderBy
626 parseUrlPiece "TermAsc" = pure TermAsc
627 parseUrlPiece "TermDesc" = pure TermDesc
628 parseUrlPiece "ScoreAsc" = pure ScoreAsc
629 parseUrlPiece "ScoreDesc" = pure ScoreDesc
630 parseUrlPiece _ = Left "Unexpected value of OrderBy"
633 instance ToParamSchema OrderBy
634 instance FromJSON OrderBy
635 instance ToJSON OrderBy
636 instance ToSchema OrderBy
637 instance Arbitrary OrderBy
639 arbitrary = elements [minBound..maxBound]
641 needsScores :: Maybe OrderBy -> Bool
642 needsScores (Just ScoreAsc) = True
643 needsScores (Just ScoreDesc) = True
644 needsScores _ = False
646 type TableNgramsApiGet = Summary " Table Ngrams API Get"
647 :> QueryParamR "ngramsType" TabType
648 :> QueryParamR "list" ListId
649 :> QueryParamR "limit" Limit
650 :> QueryParam "offset" Offset
651 :> QueryParam "listType" ListType
652 :> QueryParam "minTermSize" MinSize
653 :> QueryParam "maxTermSize" MaxSize
654 :> QueryParam "orderBy" OrderBy
655 :> QueryParam "search" Text
656 :> Get '[JSON] (VersionedWithCount NgramsTable)
658 type TableNgramsApiPut = Summary " Table Ngrams API Change"
659 :> QueryParamR "ngramsType" TabType
660 :> QueryParamR "list" ListId
661 :> ReqBody '[JSON] (Versioned NgramsTablePatch)
662 :> Put '[JSON] (Versioned NgramsTablePatch)
664 type RecomputeScoresNgramsApiGet = Summary " Recompute scores for ngrams table"
665 :> QueryParamR "ngramsType" TabType
666 :> QueryParamR "list" ListId
667 :> "recompute" :> Post '[JSON] Int
669 type TableNgramsApiGetVersion = Summary " Table Ngrams API Get Version"
670 :> QueryParamR "ngramsType" TabType
671 :> QueryParamR "list" ListId
672 :> Get '[JSON] Version
674 type TableNgramsApi = TableNgramsApiGet
675 :<|> TableNgramsApiPut
676 :<|> RecomputeScoresNgramsApiGet
677 :<|> "version" :> TableNgramsApiGetVersion
678 :<|> TableNgramsAsyncApi
680 type TableNgramsAsyncApi = Summary "Table Ngrams Async API"
684 :> AsyncJobs JobLog '[JSON] UpdateTableNgramsCharts JobLog
686 getTableNgramsCorpus :: (RepoCmdM env err m, HasNodeError err, HasConnectionPool env, HasConfig env)
693 -> Maybe MinSize -> Maybe MaxSize
695 -> Maybe Text -- full text search
696 -> m (VersionedWithCount NgramsTable)
697 getTableNgramsCorpus nId tabType listId limit_ offset listType minSize maxSize orderBy mt =
698 getTableNgrams NodeCorpus nId tabType listId limit_ offset listType minSize maxSize orderBy searchQuery
700 searchQuery (NgramsTerm nt) = maybe (const True) isInfixOf mt nt
702 getTableNgramsVersion :: (RepoCmdM env err m, HasNodeError err, HasConnectionPool env, HasConfig env)
707 getTableNgramsVersion _nId _tabType _listId = currentVersion
709 -- Versioned { _v_version = v } <- getTableNgramsCorpus nId tabType listId 100000 Nothing Nothing Nothing Nothing Nothing Nothing
710 -- This line above looks like a waste of computation to finally get only the version.
711 -- See the comment about listNgramsChangedSince.
714 -- | Text search is deactivated for now for ngrams by doc only
715 getTableNgramsDoc :: (RepoCmdM env err m, HasNodeError err, HasConnectionPool env, HasConfig env)
717 -> ListId -> Limit -> Maybe Offset
719 -> Maybe MinSize -> Maybe MaxSize
721 -> Maybe Text -- full text search
722 -> m (VersionedWithCount NgramsTable)
723 getTableNgramsDoc dId tabType listId limit_ offset listType minSize maxSize orderBy _mt = do
724 ns <- selectNodesWithUsername NodeList userMaster
725 let ngramsType = ngramsTypeFromTabType tabType
726 ngs <- selectNgramsByDoc (ns <> [listId]) dId ngramsType
727 let searchQuery (NgramsTerm nt) = flip S.member (S.fromList ngs) nt
728 getTableNgrams NodeDocument dId tabType listId limit_ offset listType minSize maxSize orderBy searchQuery
732 apiNgramsTableCorpus :: ( GargServerC env err m
734 => NodeId -> ServerT TableNgramsApi m
735 apiNgramsTableCorpus cId = getTableNgramsCorpus cId
737 :<|> scoresRecomputeTableNgrams cId
738 :<|> getTableNgramsVersion cId
739 :<|> apiNgramsAsync cId
741 apiNgramsTableDoc :: ( GargServerC env err m
743 => DocId -> ServerT TableNgramsApi m
744 apiNgramsTableDoc dId = getTableNgramsDoc dId
746 :<|> scoresRecomputeTableNgrams dId
747 :<|> getTableNgramsVersion dId
748 :<|> apiNgramsAsync dId
749 -- > index all the corpus accordingly (TODO AD)
751 apiNgramsAsync :: NodeId -> GargServer TableNgramsAsyncApi
752 apiNgramsAsync _dId =
754 JobFunction $ \i log ->
757 printDebug "tableNgramsPostChartsAsync" x
759 in tableNgramsPostChartsAsync i log'
761 -- Did the given list of ngrams changed since the given version?
762 -- The returned value is versioned boolean value, meaning that one always retrieve the
764 -- If the given version is negative then one simply receive the latest version and True.
765 -- Using this function is more precise than simply comparing the latest version number
766 -- with the local version number. Indeed there might be no change to this particular list
767 -- and still the version number has changed because of other lists.
769 -- Here the added value is to make a compromise between precision, computation, and bandwidth:
770 -- * currentVersion: good computation, good bandwidth, bad precision.
771 -- * listNgramsChangedSince: good precision, good bandwidth, bad computation.
772 -- * tableNgramsPull: good precision, good bandwidth (if you use the received data!), bad computation.
773 listNgramsChangedSince :: RepoCmdM env err m
774 => ListId -> TableNgrams.NgramsType -> Version -> m (Versioned Bool)
775 listNgramsChangedSince listId ngramsType version
777 Versioned <$> currentVersion <*> pure True
779 tableNgramsPull listId ngramsType version & mapped . v_data %~ (== mempty)