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 #-}
24 {-# OPTIONS -fno-warn-orphans #-}
26 module Gargantext.API.Ngrams
33 --, rmListNgrams TODO fix before exporting
36 , apiNgramsTableCorpus
60 , NgramsRepoElement(..)
69 , ngramsTypeFromTabType
87 , listNgramsChangedSince
91 import Codec.Serialise (Serialise())
92 import Control.Category ((>>>))
93 import Control.Concurrent
94 import Control.Lens (makeLenses, makePrisms, Getter, Iso', iso, from, (.~), (?=), (#), to, folded, {-withIndex, ifolded,-} view, use, (^.), (^..), (^?), (+~), (%~), (.~), (%=), sumOf, at, _Just, Each(..), itraverse_, both, forOf_, (%%~), (?~), mapped)
95 import Control.Monad.Error.Class (MonadError)
96 import Control.Monad.Reader
97 import Control.Monad.State
98 import Control.Monad.Trans.Control (MonadBaseControl)
99 import Data.Aeson hiding ((.=))
100 import Data.Aeson.TH (deriveJSON)
101 import qualified Data.Aeson.Text as DAT
102 import Data.Either (Either(..))
104 import qualified Data.HashMap.Strict.InsOrd as InsOrdHashMap
105 import qualified Data.List as List
106 import Data.Map.Strict (Map)
107 import qualified Data.Map.Strict as Map
108 import qualified Data.Map.Strict.Patch as PM
109 import Data.Maybe (fromMaybe)
111 import Data.Ord (Down(..))
112 import Data.Patch.Class (Replace, replace, Action(act), Group, Applicable(..), Composable(..), Transformable(..),
113 PairPatch(..), Patched, ConflictResolution, ConflictResolutionReplace, ours,
114 MaybePatch(Mod), unMod, old, new)
115 import Data.Set (Set)
116 import qualified Data.Set as S
117 import qualified Data.Set as Set
118 import Data.String (IsString, fromString)
119 import Data.Swagger hiding (version, patch)
120 import Data.Text (Text, isInfixOf, pack, strip, unpack)
121 import Data.Text.Lazy.IO as DTL
123 import Database.PostgreSQL.Simple.FromField (FromField, fromField, ResultError(ConversionFailed), returnError)
124 import Formatting (hprint, int, (%))
125 import Formatting.Clock (timeSpecs)
126 import GHC.Generics (Generic)
127 import Servant hiding (Patch)
128 import System.Clock (getTime, TimeSpec, Clock(..))
129 import System.FileLock (FileLock)
130 import System.IO (stderr)
131 import Test.QuickCheck (elements, frequency)
132 import Test.QuickCheck.Arbitrary (Arbitrary, arbitrary)
134 import Prelude (error)
135 import Protolude (maybeToEither)
136 import Gargantext.Prelude
138 import Gargantext.Core.Text (size)
139 import Gargantext.Core.Types (ListType(..), NodeId, ListId, DocId, Limit, Offset, HasInvalidError, assertValid)
140 import Gargantext.Core.Types (TODO)
141 import Gargantext.Core.Utils.Prefix (unPrefix, unPrefixUntagged, unPrefixSwagger, wellNamedSchema)
142 import Gargantext.Database.Action.Metrics.NgramsByNode (getOccByNgramsOnlyFast')
143 import Gargantext.Database.Query.Table.Node.Select
144 import Gargantext.Database.Query.Table.Ngrams hiding (NgramsType(..), ngrams, ngramsType, ngrams_terms)
145 import Gargantext.Database.Admin.Config (userMaster)
146 import Gargantext.Database.Query.Table.Node.Error (HasNodeError)
147 import Gargantext.Database.Admin.Types.Node (NodeType(..))
148 import Gargantext.Database.Prelude (fromField', HasConnectionPool, HasConfig)
149 import qualified Gargantext.Database.Query.Table.Ngrams as TableNgrams
151 ------------------------------------------------------------------------
152 --data FacetFormat = Table | Chart
153 data TabType = Docs | Trash | MoreFav | MoreTrash
154 | Terms | Sources | Authors | Institutes
156 deriving (Generic, Enum, Bounded, Show)
158 instance FromHttpApiData TabType
160 parseUrlPiece "Docs" = pure Docs
161 parseUrlPiece "Trash" = pure Trash
162 parseUrlPiece "MoreFav" = pure MoreFav
163 parseUrlPiece "MoreTrash" = pure MoreTrash
165 parseUrlPiece "Terms" = pure Terms
166 parseUrlPiece "Sources" = pure Sources
167 parseUrlPiece "Institutes" = pure Institutes
168 parseUrlPiece "Authors" = pure Authors
170 parseUrlPiece "Contacts" = pure Contacts
172 parseUrlPiece _ = Left "Unexpected value of TabType"
174 instance ToParamSchema TabType
175 instance ToJSON TabType
176 instance FromJSON TabType
177 instance ToSchema TabType
178 instance Arbitrary TabType
180 arbitrary = elements [minBound .. maxBound]
182 newtype MSet a = MSet (Map a ())
183 deriving (Eq, Ord, Show, Generic, Arbitrary, Semigroup, Monoid)
185 instance ToJSON a => ToJSON (MSet a) where
186 toJSON (MSet m) = toJSON (Map.keys m)
187 toEncoding (MSet m) = toEncoding (Map.keys m)
189 mSetFromSet :: Set a -> MSet a
190 mSetFromSet = MSet . Map.fromSet (const ())
192 mSetFromList :: Ord a => [a] -> MSet a
193 mSetFromList = MSet . Map.fromList . map (\x -> (x, ()))
195 -- mSetToSet :: Ord a => MSet a -> Set a
196 -- mSetToSet (MSet a) = Set.fromList ( Map.keys a)
197 mSetToSet :: Ord a => MSet a -> Set a
198 mSetToSet = Set.fromList . mSetToList
200 mSetToList :: MSet a -> [a]
201 mSetToList (MSet a) = Map.keys a
203 instance Foldable MSet where
204 foldMap f (MSet m) = Map.foldMapWithKey (\k _ -> f k) m
206 instance (Ord a, FromJSON a) => FromJSON (MSet a) where
207 parseJSON = fmap mSetFromList . parseJSON
209 instance (ToJSONKey a, ToSchema a) => ToSchema (MSet a) where
211 declareNamedSchema _ = wellNamedSchema "" (Proxy :: Proxy TODO)
213 ------------------------------------------------------------------------
214 newtype NgramsTerm = NgramsTerm { unNgramsTerm :: Text }
215 deriving (Ord, Eq, Show, Generic, ToJSONKey, ToJSON, FromJSON, Semigroup, Arbitrary, Serialise, ToSchema)
217 instance FromJSONKey NgramsTerm where
218 fromJSONKey = FromJSONKeyTextParser $ \t -> pure $ NgramsTerm $ strip t
220 instance IsString NgramsTerm where
221 fromString s = NgramsTerm $ pack s
223 instance FromField NgramsTerm
225 fromField field mb = do
226 v <- fromField field mb
228 Success a -> pure $ NgramsTerm $ strip a
229 Error _err -> returnError ConversionFailed field
230 $ List.intercalate " " [ "cannot parse hyperdata for JSON: "
234 data RootParent = RootParent
235 { _rp_root :: NgramsTerm
236 , _rp_parent :: NgramsTerm
238 deriving (Ord, Eq, Show, Generic)
240 deriveJSON (unPrefix "_rp_") ''RootParent
241 makeLenses ''RootParent
243 data NgramsRepoElement = NgramsRepoElement
245 , _nre_list :: ListType
246 --, _nre_root_parent :: Maybe RootParent
247 , _nre_root :: Maybe NgramsTerm
248 , _nre_parent :: Maybe NgramsTerm
249 , _nre_children :: MSet NgramsTerm
251 deriving (Ord, Eq, Show, Generic)
253 deriveJSON (unPrefix "_nre_") ''NgramsRepoElement
255 -- if ngrams & not size => size
258 makeLenses ''NgramsRepoElement
260 instance ToSchema NgramsRepoElement where
261 declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "_nre_")
263 instance Serialise (MSet NgramsTerm)
264 instance Serialise NgramsRepoElement
267 NgramsElement { _ne_ngrams :: NgramsTerm
269 , _ne_list :: ListType
270 , _ne_occurrences :: Int
271 , _ne_root :: Maybe NgramsTerm
272 , _ne_parent :: Maybe NgramsTerm
273 , _ne_children :: MSet NgramsTerm
275 deriving (Ord, Eq, Show, Generic)
277 deriveJSON (unPrefix "_ne_") ''NgramsElement
278 makeLenses ''NgramsElement
280 mkNgramsElement :: NgramsTerm
285 mkNgramsElement ngrams list rp children =
286 NgramsElement ngrams (size (unNgramsTerm ngrams)) list 1 (_rp_root <$> rp) (_rp_parent <$> rp) children
288 newNgramsElement :: Maybe ListType -> NgramsTerm -> NgramsElement
289 newNgramsElement mayList ngrams =
290 mkNgramsElement ngrams (fromMaybe MapTerm mayList) Nothing mempty
292 instance ToSchema NgramsElement where
293 declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "_ne_")
294 instance Arbitrary NgramsElement where
295 arbitrary = elements [newNgramsElement Nothing "sport"]
297 ngramsElementToRepo :: NgramsElement -> NgramsRepoElement
299 (NgramsElement { _ne_size = s
313 ngramsElementFromRepo :: NgramsTerm -> NgramsRepoElement -> NgramsElement
314 ngramsElementFromRepo
323 NgramsElement { _ne_size = s
328 , _ne_ngrams = ngrams
329 , _ne_occurrences = panic $ "API.Ngrams._ne_occurrences"
331 -- Here we could use 0 if we want to avoid any `panic`.
332 -- It will not happen using getTableNgrams if
333 -- getOccByNgramsOnly provides a count of occurrences for
334 -- all the ngrams given.
338 ------------------------------------------------------------------------
339 newtype NgramsTable = NgramsTable [NgramsElement]
340 deriving (Ord, Eq, Generic, ToJSON, FromJSON, Show)
342 type NgramsList = NgramsTable
344 makePrisms ''NgramsTable
346 -- | Question: why these repetition of Type in this instance
347 -- may you document it please ?
348 instance Each NgramsTable NgramsTable NgramsElement NgramsElement where
349 each = _NgramsTable . each
352 -- | TODO Check N and Weight
354 toNgramsElement :: [NgramsTableData] -> [NgramsElement]
355 toNgramsElement ns = map toNgramsElement' ns
357 toNgramsElement' (NgramsTableData _ p t _ lt w) = NgramsElement t lt' (round w) p' c'
361 Just x -> lookup x mapParent
362 c' = maybe mempty identity $ lookup t mapChildren
363 lt' = maybe (panic "API.Ngrams: listypeId") identity lt
365 mapParent :: Map Int Text
366 mapParent = Map.fromListWith (<>) $ map (\(NgramsTableData i _ t _ _ _) -> (i,t)) ns
368 mapChildren :: Map Text (Set Text)
369 mapChildren = Map.mapKeys (\i -> (maybe (panic "API.Ngrams.mapChildren: ParentId with no Terms: Impossible") identity $ lookup i mapParent))
370 $ Map.fromListWith (<>)
371 $ map (first fromJust)
372 $ filter (isJust . fst)
373 $ map (\(NgramsTableData _ p t _ _ _) -> (p, Set.singleton t)) ns
376 mockTable :: NgramsTable
377 mockTable = NgramsTable
378 [ mkNgramsElement "animal" MapTerm Nothing (mSetFromList ["dog", "cat"])
379 , mkNgramsElement "cat" MapTerm (rp "animal") mempty
380 , mkNgramsElement "cats" StopTerm Nothing mempty
381 , mkNgramsElement "dog" MapTerm (rp "animal") (mSetFromList ["dogs"])
382 , mkNgramsElement "dogs" StopTerm (rp "dog") mempty
383 , mkNgramsElement "fox" MapTerm Nothing mempty
384 , mkNgramsElement "object" CandidateTerm Nothing mempty
385 , mkNgramsElement "nothing" StopTerm Nothing mempty
386 , mkNgramsElement "organic" MapTerm Nothing (mSetFromList ["flower"])
387 , mkNgramsElement "flower" MapTerm (rp "organic") mempty
388 , mkNgramsElement "moon" CandidateTerm Nothing mempty
389 , mkNgramsElement "sky" StopTerm Nothing mempty
392 rp n = Just $ RootParent n n
394 instance Arbitrary NgramsTable where
395 arbitrary = pure mockTable
397 instance ToSchema NgramsTable
399 ------------------------------------------------------------------------
400 type NgramsTableMap = Map NgramsTerm NgramsRepoElement
401 ------------------------------------------------------------------------
402 -- On the Client side:
403 --data Action = InGroup NgramsId NgramsId
404 -- | OutGroup NgramsId NgramsId
405 -- | SetListType NgramsId ListType
407 data PatchSet a = PatchSet
411 deriving (Eq, Ord, Show, Generic)
413 makeLenses ''PatchSet
414 makePrisms ''PatchSet
416 instance ToJSON a => ToJSON (PatchSet a) where
417 toJSON = genericToJSON $ unPrefix "_"
418 toEncoding = genericToEncoding $ unPrefix "_"
420 instance (Ord a, FromJSON a) => FromJSON (PatchSet a) where
421 parseJSON = genericParseJSON $ unPrefix "_"
424 instance (Ord a, Arbitrary a) => Arbitrary (PatchSet a) where
425 arbitrary = PatchSet <$> arbitrary <*> arbitrary
427 type instance Patched (PatchSet a) = Set a
429 type ConflictResolutionPatchSet a = SimpleConflictResolution' (Set a)
430 type instance ConflictResolution (PatchSet a) = ConflictResolutionPatchSet a
432 instance Ord a => Semigroup (PatchSet a) where
433 p <> q = PatchSet { _rem = (q ^. rem) `Set.difference` (p ^. add) <> p ^. rem
434 , _add = (q ^. add) `Set.difference` (p ^. rem) <> p ^. add
437 instance Ord a => Monoid (PatchSet a) where
438 mempty = PatchSet mempty mempty
440 instance Ord a => Group (PatchSet a) where
441 invert (PatchSet r a) = PatchSet a r
443 instance Ord a => Composable (PatchSet a) where
444 composable _ _ = undefined
446 instance Ord a => Action (PatchSet a) (Set a) where
447 act p source = (source `Set.difference` (p ^. rem)) <> p ^. add
449 instance Applicable (PatchSet a) (Set a) where
450 applicable _ _ = mempty
452 instance Ord a => Validity (PatchSet a) where
453 validate p = check (Set.disjoint (p ^. rem) (p ^. add)) "_rem and _add should be dijoint"
455 instance Ord a => Transformable (PatchSet a) where
456 transformable = undefined
458 conflicts _p _q = undefined
460 transformWith conflict p q = undefined conflict p q
462 instance ToSchema a => ToSchema (PatchSet a)
465 type AddRem = Replace (Maybe ())
467 instance Serialise AddRem
469 remPatch, addPatch :: AddRem
470 remPatch = replace (Just ()) Nothing
471 addPatch = replace Nothing (Just ())
473 isRem :: Replace (Maybe ()) -> Bool
474 isRem = (== remPatch)
476 type PatchMap = PM.PatchMap
479 newtype PatchMSet a = PatchMSet (PatchMap a AddRem)
480 deriving (Eq, Show, Generic, Validity, Semigroup, Monoid, Group,
481 Transformable, Composable)
483 type ConflictResolutionPatchMSet a = a -> ConflictResolutionReplace (Maybe ())
484 type instance ConflictResolution (PatchMSet a) = ConflictResolutionPatchMSet a
486 instance (Serialise a, Ord a) => Serialise (PatchMap a AddRem)
487 instance (Serialise a, Ord a) => Serialise (PatchMSet a)
489 -- TODO this breaks module abstraction
490 makePrisms ''PM.PatchMap
492 makePrisms ''PatchMSet
494 _PatchMSetIso :: Ord a => Iso' (PatchMSet a) (PatchSet a)
495 _PatchMSetIso = _PatchMSet . _PatchMap . iso f g . from _PatchSet
497 f :: Ord a => Map a (Replace (Maybe ())) -> (Set a, Set a)
498 f = Map.partition isRem >>> both %~ Map.keysSet
500 g :: Ord a => (Set a, Set a) -> Map a (Replace (Maybe ()))
501 g (rems, adds) = Map.fromSet (const remPatch) rems
502 <> Map.fromSet (const addPatch) adds
504 instance Ord a => Action (PatchMSet a) (MSet a) where
505 act (PatchMSet p) (MSet m) = MSet $ act p m
507 instance Ord a => Applicable (PatchMSet a) (MSet a) where
508 applicable (PatchMSet p) (MSet m) = applicable p m
510 instance (Ord a, ToJSON a) => ToJSON (PatchMSet a) where
511 toJSON = toJSON . view _PatchMSetIso
512 toEncoding = toEncoding . view _PatchMSetIso
514 instance (Ord a, FromJSON a) => FromJSON (PatchMSet a) where
515 parseJSON = fmap (_PatchMSetIso #) . parseJSON
517 instance (Ord a, Arbitrary a) => Arbitrary (PatchMSet a) where
518 arbitrary = (PatchMSet . PM.fromMap) <$> arbitrary
520 instance ToSchema a => ToSchema (PatchMSet a) where
522 declareNamedSchema _ = wellNamedSchema "" (Proxy :: Proxy TODO)
524 type instance Patched (PatchMSet a) = MSet a
526 instance (Eq a, Arbitrary a) => Arbitrary (Replace a) where
527 arbitrary = uncurry replace <$> arbitrary
528 -- If they happen to be equal then the patch is Keep.
530 instance ToSchema a => ToSchema (Replace a) where
531 declareNamedSchema (_ :: Proxy (Replace a)) = do
532 -- TODO Keep constructor is not supported here.
533 aSchema <- declareSchemaRef (Proxy :: Proxy a)
534 return $ NamedSchema (Just "Replace") $ mempty
535 & type_ ?~ SwaggerObject
537 InsOrdHashMap.fromList
541 & required .~ [ "old", "new" ]
544 = NgramsPatch { _patch_children :: PatchMSet NgramsTerm
545 , _patch_list :: Replace ListType -- TODO Map UserId ListType
547 | NgramsReplace { _patch_old :: Maybe NgramsRepoElement
548 , _patch_new :: Maybe NgramsRepoElement
550 deriving (Eq, Show, Generic)
552 -- The JSON encoding is untagged, this is OK since the field names are disjoints and thus the encoding is unambiguous.
553 -- TODO: the empty object should be accepted and treated as mempty.
554 deriveJSON (unPrefixUntagged "_") ''NgramsPatch
555 makeLenses ''NgramsPatch
557 -- TODO: This instance is simplified since we should either have the fields children and/or list
558 -- or the fields old and/or new.
559 instance ToSchema NgramsPatch where
560 declareNamedSchema _ = do
561 childrenSch <- declareSchemaRef (Proxy :: Proxy (PatchMSet NgramsTerm))
562 listSch <- declareSchemaRef (Proxy :: Proxy (Replace ListType))
563 nreSch <- declareSchemaRef (Proxy :: Proxy NgramsRepoElement)
564 return $ NamedSchema (Just "NgramsPatch") $ mempty
565 & type_ ?~ SwaggerObject
567 InsOrdHashMap.fromList
568 [ ("children", childrenSch)
574 instance Arbitrary NgramsPatch where
575 arbitrary = frequency [ (9, NgramsPatch <$> arbitrary <*> (replace <$> arbitrary <*> arbitrary))
576 , (1, NgramsReplace <$> arbitrary <*> arbitrary)
579 instance Serialise NgramsPatch
580 instance Serialise (Replace ListType)
582 instance Serialise ListType
584 type NgramsPatchIso =
585 MaybePatch NgramsRepoElement (PairPatch (PatchMSet NgramsTerm) (Replace ListType))
587 _NgramsPatch :: Iso' NgramsPatch NgramsPatchIso
588 _NgramsPatch = iso unwrap wrap
590 unwrap (NgramsPatch c l) = Mod $ PairPatch (c, l)
591 unwrap (NgramsReplace o n) = replace o n
594 Just (PairPatch (c, l)) -> NgramsPatch c l
595 Nothing -> NgramsReplace (x ^? old . _Just) (x ^? new . _Just)
597 instance Semigroup NgramsPatch where
598 p <> q = _NgramsPatch # (p ^. _NgramsPatch <> q ^. _NgramsPatch)
600 instance Monoid NgramsPatch where
601 mempty = _NgramsPatch # mempty
603 instance Validity NgramsPatch where
604 validate p = p ^. _NgramsPatch . to validate
606 instance Transformable NgramsPatch where
607 transformable p q = transformable (p ^. _NgramsPatch) (q ^. _NgramsPatch)
609 conflicts p q = conflicts (p ^. _NgramsPatch) (q ^. _NgramsPatch)
611 transformWith conflict p q = (_NgramsPatch # p', _NgramsPatch # q')
613 (p', q') = transformWith conflict (p ^. _NgramsPatch) (q ^. _NgramsPatch)
615 type ConflictResolutionNgramsPatch =
616 ( ConflictResolutionReplace (Maybe NgramsRepoElement)
617 , ( ConflictResolutionPatchMSet NgramsTerm
618 , ConflictResolutionReplace ListType
622 type instance ConflictResolution NgramsPatch =
623 ConflictResolutionNgramsPatch
625 type PatchedNgramsPatch = Maybe NgramsRepoElement
626 type instance Patched NgramsPatch = PatchedNgramsPatch
628 instance Applicable (PairPatch (PatchMSet NgramsTerm) (Replace ListType)) NgramsRepoElement where
629 applicable (PairPatch (c, l)) n = applicable c (n ^. nre_children) <> applicable l (n ^. nre_list)
631 instance Action (PairPatch (PatchMSet NgramsTerm) (Replace ListType)) NgramsRepoElement where
632 act (PairPatch (c, l)) = (nre_children %~ act c)
633 . (nre_list %~ act l)
635 instance Applicable NgramsPatch (Maybe NgramsRepoElement) where
636 applicable p = applicable (p ^. _NgramsPatch)
638 instance Action NgramsPatch (Maybe NgramsRepoElement) where
639 act p = act (p ^. _NgramsPatch)
641 newtype NgramsTablePatch = NgramsTablePatch (PatchMap NgramsTerm NgramsPatch)
642 deriving (Eq, Show, Generic, ToJSON, FromJSON, Semigroup, Monoid, Validity, Transformable)
644 instance Serialise NgramsTablePatch
645 instance Serialise (PatchMap NgramsTerm NgramsPatch)
647 instance FromField NgramsTablePatch
649 fromField = fromField'
651 instance FromField (PatchMap TableNgrams.NgramsType (PatchMap NodeId NgramsTablePatch))
653 fromField = fromField'
655 type instance ConflictResolution NgramsTablePatch =
656 NgramsTerm -> ConflictResolutionNgramsPatch
658 type PatchedNgramsTablePatch = Map NgramsTerm PatchedNgramsPatch
659 -- ~ Patched (PatchMap NgramsTerm NgramsPatch)
660 type instance Patched NgramsTablePatch = PatchedNgramsTablePatch
662 makePrisms ''NgramsTablePatch
663 instance ToSchema (PatchMap NgramsTerm NgramsPatch)
664 instance ToSchema NgramsTablePatch
666 instance Applicable NgramsTablePatch (Maybe NgramsTableMap) where
667 applicable p = applicable (p ^. _NgramsTablePatch)
669 instance Action NgramsTablePatch (Maybe NgramsTableMap) where
671 fmap (execState (reParentNgramsTablePatch p)) .
672 act (p ^. _NgramsTablePatch)
674 instance Arbitrary NgramsTablePatch where
675 arbitrary = NgramsTablePatch <$> PM.fromMap <$> arbitrary
677 -- Should it be less than an Lens' to preserve PatchMap's abstraction.
678 -- ntp_ngrams_patches :: Lens' NgramsTablePatch (Map NgramsTerm NgramsPatch)
679 -- ntp_ngrams_patches = _NgramsTablePatch . undefined
681 type ReParent a = forall m. MonadState NgramsTableMap m => a -> m ()
683 reRootChildren :: NgramsTerm -> ReParent NgramsTerm
684 reRootChildren root ngram = do
685 nre <- use $ at ngram
686 forOf_ (_Just . nre_children . folded) nre $ \child -> do
687 at child . _Just . nre_root ?= root
688 reRootChildren root child
690 reParent :: Maybe RootParent -> ReParent NgramsTerm
691 reParent rp child = do
692 at child . _Just %= ( (nre_parent .~ (_rp_parent <$> rp))
693 . (nre_root .~ (_rp_root <$> rp))
695 reRootChildren (fromMaybe child (rp ^? _Just . rp_root)) child
697 reParentAddRem :: RootParent -> NgramsTerm -> ReParent AddRem
698 reParentAddRem rp child p =
699 reParent (if isRem p then Nothing else Just rp) child
701 reParentNgramsPatch :: NgramsTerm -> ReParent NgramsPatch
702 reParentNgramsPatch parent ngramsPatch = do
703 root_of_parent <- use (at parent . _Just . nre_root)
705 root = fromMaybe parent root_of_parent
706 rp = RootParent { _rp_root = root, _rp_parent = parent }
707 itraverse_ (reParentAddRem rp) (ngramsPatch ^. patch_children . _PatchMSet . _PatchMap)
708 -- TODO FoldableWithIndex/TraversableWithIndex for PatchMap
710 reParentNgramsTablePatch :: ReParent NgramsTablePatch
711 reParentNgramsTablePatch p = itraverse_ reParentNgramsPatch (p ^. _NgramsTablePatch. _PatchMap)
712 -- TODO FoldableWithIndex/TraversableWithIndex for PatchMap
714 ------------------------------------------------------------------------
715 ------------------------------------------------------------------------
718 data Versioned a = Versioned
719 { _v_version :: Version
722 deriving (Generic, Show, Eq)
723 deriveJSON (unPrefix "_v_") ''Versioned
724 makeLenses ''Versioned
725 instance (Typeable a, ToSchema a) => ToSchema (Versioned a) where
726 declareNamedSchema = wellNamedSchema "_v_"
727 instance Arbitrary a => Arbitrary (Versioned a) where
728 arbitrary = Versioned 1 <$> arbitrary -- TODO 1 is constant so far
732 -- TODO sequences of modifications (Patchs)
733 type NgramsIdPatch = Patch NgramsId NgramsPatch
735 ngramsPatch :: Int -> NgramsPatch
736 ngramsPatch n = NgramsPatch (DM.fromList [(1, StopTerm)]) (Set.fromList [n]) Set.empty
738 toEdit :: NgramsId -> NgramsPatch -> Edit NgramsId NgramsPatch
739 toEdit n p = Edit n p
740 ngramsIdPatch :: Patch NgramsId NgramsPatch
741 ngramsIdPatch = fromList $ catMaybes $ reverse [ replace (1::NgramsId) (Just $ ngramsPatch 1) Nothing
742 , replace (1::NgramsId) Nothing (Just $ ngramsPatch 2)
743 , replace (2::NgramsId) Nothing (Just $ ngramsPatch 2)
746 -- applyPatchBack :: Patch -> IO Patch
747 -- isEmptyPatch = Map.all (\x -> Set.isEmpty (add_children x) && Set.isEmpty ... )
749 ------------------------------------------------------------------------
750 ------------------------------------------------------------------------
751 ------------------------------------------------------------------------
754 -- TODO: Replace.old is ignored which means that if the current list
755 -- `MapTerm` and that the patch is `Replace CandidateTerm StopTerm` then
756 -- the list is going to be `StopTerm` while it should keep `MapTerm`.
757 -- However this should not happen in non conflicting situations.
758 mkListsUpdate :: NgramsType -> NgramsTablePatch -> [(NgramsTypeId, NgramsTerm, ListTypeId)]
759 mkListsUpdate nt patches =
760 [ (ngramsTypeId nt, ng, listTypeId lt)
761 | (ng, patch) <- patches ^.. ntp_ngrams_patches . ifolded . withIndex
762 , lt <- patch ^.. patch_list . new
765 mkChildrenGroups :: (PatchSet NgramsTerm -> Set NgramsTerm)
768 -> [(NgramsTypeId, NgramsParent, NgramsChild)]
769 mkChildrenGroups addOrRem nt patches =
770 [ (ngramsTypeId nt, parent, child)
771 | (parent, patch) <- patches ^.. ntp_ngrams_patches . ifolded . withIndex
772 , child <- patch ^.. patch_children . to addOrRem . folded
776 ngramsTypeFromTabType :: TabType -> TableNgrams.NgramsType
777 ngramsTypeFromTabType tabType =
778 let lieu = "Garg.API.Ngrams: " :: Text in
780 Sources -> TableNgrams.Sources
781 Authors -> TableNgrams.Authors
782 Institutes -> TableNgrams.Institutes
783 Terms -> TableNgrams.NgramsTerms
784 _ -> panic $ lieu <> "No Ngrams for this tab"
785 -- TODO: This `panic` would disapear with custom NgramsType.
787 ------------------------------------------------------------------------
789 { _r_version :: Version
792 -- first patch in the list is the most recent
796 instance (FromJSON s, FromJSON p) => FromJSON (Repo s p) where
797 parseJSON = genericParseJSON $ unPrefix "_r_"
799 instance (ToJSON s, ToJSON p) => ToJSON (Repo s p) where
800 toJSON = genericToJSON $ unPrefix "_r_"
801 toEncoding = genericToEncoding $ unPrefix "_r_"
803 instance (Serialise s, Serialise p) => Serialise (Repo s p)
807 initRepo :: Monoid s => Repo s p
808 initRepo = Repo 1 mempty []
810 type NgramsRepo = Repo NgramsState NgramsStatePatch
811 type NgramsState = Map TableNgrams.NgramsType (Map NodeId NgramsTableMap)
812 type NgramsStatePatch = PatchMap TableNgrams.NgramsType (PatchMap NodeId NgramsTablePatch)
814 instance Serialise (PM.PatchMap NodeId NgramsTablePatch)
815 instance Serialise NgramsStatePatch
817 initMockRepo :: NgramsRepo
818 initMockRepo = Repo 1 s []
820 s = Map.singleton TableNgrams.NgramsTerms
821 $ Map.singleton 47254
823 [ (n ^. ne_ngrams, ngramsElementToRepo n) | n <- mockTable ^. _NgramsTable ]
825 data RepoEnv = RepoEnv
826 { _renv_var :: !(MVar NgramsRepo)
827 , _renv_saver :: !(IO ())
828 , _renv_lock :: !FileLock
834 class HasRepoVar env where
835 repoVar :: Getter env (MVar NgramsRepo)
837 instance HasRepoVar (MVar NgramsRepo) where
840 class HasRepoSaver env where
841 repoSaver :: Getter env (IO ())
843 class (HasRepoVar env, HasRepoSaver env) => HasRepo env where
844 repoEnv :: Getter env RepoEnv
846 instance HasRepo RepoEnv where
849 instance HasRepoVar RepoEnv where
852 instance HasRepoSaver RepoEnv where
853 repoSaver = renv_saver
855 type RepoCmdM env err m =
858 , MonadBaseControl IO m
861 ------------------------------------------------------------------------
863 saveRepo :: ( MonadReader env m, MonadBase IO m, HasRepoSaver env )
865 saveRepo = liftBase =<< view repoSaver
867 listTypeConflictResolution :: ListType -> ListType -> ListType
868 listTypeConflictResolution _ _ = undefined -- TODO Use Map User ListType
870 ngramsStatePatchConflictResolution
871 :: TableNgrams.NgramsType
874 -> ConflictResolutionNgramsPatch
875 ngramsStatePatchConflictResolution _ngramsType _nodeId _ngramsTerm
876 = (ours, (const ours, ours), (False, False))
877 -- (False, False) mean here that Mod has always priority.
878 -- (True, False) <- would mean priority to the left (same as ours).
880 -- undefined {- TODO think this through -}, listTypeConflictResolution)
883 -- Insertions are not considered as patches,
884 -- they do not extend history,
885 -- they do not bump version.
886 insertNewOnly :: a -> Maybe b -> a
887 insertNewOnly m = maybe m (const $ error "insertNewOnly: impossible")
888 -- TODO error handling
890 something :: Monoid a => Maybe a -> a
891 something Nothing = mempty
892 something (Just a) = a
895 -- TODO refactor with putListNgrams
896 copyListNgrams :: RepoCmdM env err m
897 => NodeId -> NodeId -> NgramsType
899 copyListNgrams srcListId dstListId ngramsType = do
901 liftBase $ modifyMVar_ var $
902 pure . (r_state . at ngramsType %~ (Just . f . something))
905 f :: Map NodeId NgramsTableMap -> Map NodeId NgramsTableMap
906 f m = m & at dstListId %~ insertNewOnly (m ^. at srcListId)
908 -- TODO refactor with putListNgrams
909 -- The list must be non-empty!
910 -- The added ngrams must be non-existent!
911 addListNgrams :: RepoCmdM env err m
912 => NodeId -> NgramsType
913 -> [NgramsElement] -> m ()
914 addListNgrams listId ngramsType nes = do
916 liftBase $ modifyMVar_ var $
917 pure . (r_state . at ngramsType . _Just . at listId . _Just <>~ m)
920 m = Map.fromList $ (\n -> (n ^. ne_ngrams, n)) <$> nes
924 rmListNgrams :: RepoCmdM env err m
926 -> TableNgrams.NgramsType
928 rmListNgrams l nt = setListNgrams l nt mempty
930 -- | TODO: incr the Version number
931 -- && should use patch
933 setListNgrams :: RepoCmdM env err m
935 -> TableNgrams.NgramsType
936 -> Map NgramsTerm NgramsRepoElement
938 setListNgrams listId ngramsType ns = do
940 liftBase $ modifyMVar_ var $
944 (at listId .~ ( Just ns))
951 -- This is no longer part of the API.
952 -- This function is maintained for its usage in Database.Action.Flow.List.
953 -- If the given list of ngrams elements contains ngrams already in
954 -- the repo, they will be ignored.
955 putListNgrams :: (HasInvalidError err, RepoCmdM env err m)
957 -> TableNgrams.NgramsType
960 putListNgrams _ _ [] = pure ()
961 putListNgrams nodeId ngramsType nes = putListNgrams' nodeId ngramsType m
963 m = Map.fromList $ map (\n -> (n ^. ne_ngrams, ngramsElementToRepo n)) nes
965 putListNgrams' :: (HasInvalidError err, RepoCmdM env err m)
967 -> TableNgrams.NgramsType
968 -> Map NgramsTerm NgramsRepoElement
970 putListNgrams' nodeId ngramsType ns = do
971 -- printDebug "[putListNgrams'] nodeId" nodeId
972 -- printDebug "[putListNgrams'] ngramsType" ngramsType
973 -- printDebug "[putListNgrams'] ns" ns
975 let p1 = NgramsTablePatch . PM.fromMap $ NgramsReplace Nothing . Just <$> ns
976 (p0, p0_validity) = PM.singleton nodeId p1
977 (p, p_validity) = PM.singleton ngramsType p0
978 assertValid p0_validity
979 assertValid p_validity
983 q <- commitStatePatch (Versioned v p)
985 -- What if another commit comes in between?
986 -- Shall we have a blindCommitStatePatch? It would not ask for a version but just a patch.
987 -- The modifyMVar_ would test the patch with applicable first.
988 -- If valid the rest would be atomic and no merge is required.
991 liftBase $ modifyMVar_ var $ \r -> do
992 pure $ r & r_version +~ 1
994 & r_state . at ngramsType %~
1007 currentVersion :: RepoCmdM env err m
1011 r <- liftBase $ readMVar var
1012 pure $ r ^. r_version
1015 -- tableNgramsPut :: (HasInvalidError err, RepoCmdM env err m)
1016 commitStatePatch :: RepoCmdM env err m => Versioned NgramsStatePatch -> m (Versioned NgramsStatePatch)
1017 commitStatePatch (Versioned p_version p) = do
1019 vq' <- liftBase $ modifyMVar var $ \r -> do
1021 q = mconcat $ take (r ^. r_version - p_version) (r ^. r_history)
1022 (p', q') = transformWith ngramsStatePatchConflictResolution p q
1023 r' = r & r_version +~ 1
1025 & r_history %~ (p' :)
1027 -- Ideally we would like to check these properties. However:
1028 -- * They should be checked only to debug the code. The client data
1029 -- should be able to trigger these.
1030 -- * What kind of error should they throw (we are in IO here)?
1031 -- * Should we keep modifyMVar?
1032 -- * Should we throw the validation in an Exception, catch it around
1033 -- modifyMVar and throw it back as an Error?
1034 assertValid $ transformable p q
1035 assertValid $ applicable p' (r ^. r_state)
1037 pure (r', Versioned (r' ^. r_version) q')
1042 -- This is a special case of tableNgramsPut where the input patch is empty.
1043 tableNgramsPull :: RepoCmdM env err m
1045 -> TableNgrams.NgramsType
1047 -> m (Versioned NgramsTablePatch)
1048 tableNgramsPull listId ngramsType p_version = do
1050 r <- liftBase $ readMVar var
1053 q = mconcat $ take (r ^. r_version - p_version) (r ^. r_history)
1054 q_table = q ^. _PatchMap . at ngramsType . _Just . _PatchMap . at listId . _Just
1056 pure (Versioned (r ^. r_version) q_table)
1058 -- Apply the given patch to the DB and returns the patch to be applied on the
1060 -- TODO-ACCESS check
1061 tableNgramsPut :: (HasInvalidError err, RepoCmdM env err m)
1064 -> Versioned NgramsTablePatch
1065 -> m (Versioned NgramsTablePatch)
1066 tableNgramsPut tabType listId (Versioned p_version p_table)
1067 | p_table == mempty = do
1068 let ngramsType = ngramsTypeFromTabType tabType
1069 tableNgramsPull listId ngramsType p_version
1072 let ngramsType = ngramsTypeFromTabType tabType
1073 (p0, p0_validity) = PM.singleton listId p_table
1074 (p, p_validity) = PM.singleton ngramsType p0
1076 assertValid p0_validity
1077 assertValid p_validity
1079 commitStatePatch (Versioned p_version p)
1080 <&> v_data %~ (view (_PatchMap . at ngramsType . _Just . _PatchMap . at listId . _Just))
1082 mergeNgramsElement :: NgramsRepoElement -> NgramsRepoElement -> NgramsRepoElement
1083 mergeNgramsElement _neOld neNew = neNew
1085 { _ne_list :: ListType
1086 If we merge the parents/children we can potentially create cycles!
1087 , _ne_parent :: Maybe NgramsTerm
1088 , _ne_children :: MSet NgramsTerm
1092 getNgramsTableMap :: RepoCmdM env err m
1094 -> TableNgrams.NgramsType
1095 -> m (Versioned NgramsTableMap)
1096 getNgramsTableMap nodeId ngramsType = do
1098 repo <- liftBase $ readMVar v
1099 pure $ Versioned (repo ^. r_version)
1100 (repo ^. r_state . at ngramsType . _Just . at nodeId . _Just)
1102 dumpJsonTableMap :: RepoCmdM env err m
1105 -> TableNgrams.NgramsType
1107 dumpJsonTableMap fpath nodeId ngramsType = do
1108 m <- getNgramsTableMap nodeId ngramsType
1109 liftBase $ DTL.writeFile (unpack fpath) (DAT.encodeToLazyText m)
1115 -- | TODO Errors management
1116 -- TODO: polymorphic for Annuaire or Corpus or ...
1117 -- | Table of Ngrams is a ListNgrams formatted (sorted and/or cut).
1118 -- TODO: should take only one ListId
1120 getTime' :: MonadBase IO m => m TimeSpec
1121 getTime' = liftBase $ getTime ProcessCPUTime
1124 getTableNgrams :: forall env err m.
1125 (RepoCmdM env err m, HasNodeError err, HasConnectionPool env, HasConfig env)
1126 => NodeType -> NodeId -> TabType
1127 -> ListId -> Limit -> Maybe Offset
1129 -> Maybe MinSize -> Maybe MaxSize
1131 -> (NgramsTerm -> Bool)
1132 -> m (Versioned NgramsTable)
1133 getTableNgrams _nType nId tabType listId limit_ offset
1134 listType minSize maxSize orderBy searchQuery = do
1137 -- lIds <- selectNodesWithUsername NodeList userMaster
1139 ngramsType = ngramsTypeFromTabType tabType
1140 offset' = maybe 0 identity offset
1141 listType' = maybe (const True) (==) listType
1142 minSize' = maybe (const True) (<=) minSize
1143 maxSize' = maybe (const True) (>=) maxSize
1145 selected_node n = minSize' s
1147 && searchQuery (n ^. ne_ngrams)
1148 && listType' (n ^. ne_list)
1152 selected_inner roots n = maybe False (`Set.member` roots) (n ^. ne_root)
1154 ---------------------------------------
1155 sortOnOrder Nothing = identity
1156 sortOnOrder (Just TermAsc) = List.sortOn $ view ne_ngrams
1157 sortOnOrder (Just TermDesc) = List.sortOn $ Down . view ne_ngrams
1158 sortOnOrder (Just ScoreAsc) = List.sortOn $ view ne_occurrences
1159 sortOnOrder (Just ScoreDesc) = List.sortOn $ Down . view ne_occurrences
1161 ---------------------------------------
1162 selectAndPaginate :: Map NgramsTerm NgramsElement -> [NgramsElement]
1163 selectAndPaginate tableMap = roots <> inners
1165 list = tableMap ^.. each
1166 rootOf ne = maybe ne (\r -> fromMaybe (panic "getTableNgrams: invalid root") (tableMap ^. at r))
1168 selected_nodes = list & take limit_
1170 . filter selected_node
1171 . sortOnOrder orderBy
1172 roots = rootOf <$> selected_nodes
1173 rootsSet = Set.fromList (_ne_ngrams <$> roots)
1174 inners = list & filter (selected_inner rootsSet)
1176 ---------------------------------------
1177 setScores :: forall t. Each t t NgramsElement NgramsElement => Bool -> t -> m t
1178 setScores False table = pure table
1179 setScores True table = do
1180 let ngrams_terms = unNgramsTerm <$> (table ^.. each . ne_ngrams)
1182 occurrences <- getOccByNgramsOnlyFast' nId
1187 liftBase $ hprint stderr
1188 ("getTableNgrams/setScores #ngrams=" % int % " time=" % timeSpecs % "\n")
1189 (length ngrams_terms) t1 t2
1191 occurrences <- getOccByNgramsOnlySlow nType nId
1197 setOcc ne = ne & ne_occurrences .~ sumOf (at (unNgramsTerm (ne ^. ne_ngrams)) . _Just) occurrences
1199 pure $ table & each %~ setOcc
1200 ---------------------------------------
1202 -- lists <- catMaybes <$> listsWith userMaster
1203 -- trace (show lists) $
1204 -- getNgramsTableMap ({-lists <>-} listIds) ngramsType
1206 let scoresNeeded = needsScores orderBy
1207 tableMap1 <- getNgramsTableMap listId ngramsType
1209 tableMap2 <- tableMap1 & v_data %%~ setScores scoresNeeded
1210 . Map.mapWithKey ngramsElementFromRepo
1212 tableMap3 <- tableMap2 & v_data %%~ fmap NgramsTable
1213 . setScores (not scoresNeeded)
1216 liftBase $ hprint stderr
1217 ("getTableNgrams total=" % timeSpecs
1218 % " map1=" % timeSpecs
1219 % " map2=" % timeSpecs
1220 % " map3=" % timeSpecs
1221 % " sql=" % (if scoresNeeded then "map2" else "map3")
1223 ) t0 t3 t0 t1 t1 t2 t2 t3
1227 scoresRecomputeTableNgrams :: forall env err m. (RepoCmdM env err m, HasNodeError err, HasConnectionPool env, HasConfig env) => NodeId -> TabType -> ListId -> m Int
1228 scoresRecomputeTableNgrams nId tabType listId = do
1229 tableMap <- getNgramsTableMap listId ngramsType
1230 _ <- tableMap & v_data %%~ setScores
1231 . Map.mapWithKey ngramsElementFromRepo
1235 ngramsType = ngramsTypeFromTabType tabType
1237 setScores :: forall t. Each t t NgramsElement NgramsElement => t -> m t
1238 setScores table = do
1239 let ngrams_terms = unNgramsTerm <$> (table ^.. each . ne_ngrams)
1240 occurrences <- getOccByNgramsOnlyFast' nId
1245 setOcc ne = ne & ne_occurrences .~ sumOf (at (unNgramsTerm (ne ^. ne_ngrams)) . _Just) occurrences
1247 pure $ table & each %~ setOcc
1253 -- TODO: find a better place for the code above, All APIs stay here
1254 type QueryParamR = QueryParam' '[Required, Strict]
1256 data OrderBy = TermAsc | TermDesc | ScoreAsc | ScoreDesc
1257 deriving (Generic, Enum, Bounded, Read, Show)
1259 instance FromHttpApiData OrderBy
1261 parseUrlPiece "TermAsc" = pure TermAsc
1262 parseUrlPiece "TermDesc" = pure TermDesc
1263 parseUrlPiece "ScoreAsc" = pure ScoreAsc
1264 parseUrlPiece "ScoreDesc" = pure ScoreDesc
1265 parseUrlPiece _ = Left "Unexpected value of OrderBy"
1268 instance ToParamSchema OrderBy
1269 instance FromJSON OrderBy
1270 instance ToJSON OrderBy
1271 instance ToSchema OrderBy
1272 instance Arbitrary OrderBy
1274 arbitrary = elements [minBound..maxBound]
1276 needsScores :: Maybe OrderBy -> Bool
1277 needsScores (Just ScoreAsc) = True
1278 needsScores (Just ScoreDesc) = True
1279 needsScores _ = False
1281 type TableNgramsApiGet = Summary " Table Ngrams API Get"
1282 :> QueryParamR "ngramsType" TabType
1283 :> QueryParamR "list" ListId
1284 :> QueryParamR "limit" Limit
1285 :> QueryParam "offset" Offset
1286 :> QueryParam "listType" ListType
1287 :> QueryParam "minTermSize" MinSize
1288 :> QueryParam "maxTermSize" MaxSize
1289 :> QueryParam "orderBy" OrderBy
1290 :> QueryParam "search" Text
1291 :> Get '[JSON] (Versioned NgramsTable)
1293 type TableNgramsApiPut = Summary " Table Ngrams API Change"
1294 :> QueryParamR "ngramsType" TabType
1295 :> QueryParamR "list" ListId
1296 :> ReqBody '[JSON] (Versioned NgramsTablePatch)
1297 :> Put '[JSON] (Versioned NgramsTablePatch)
1299 type RecomputeScoresNgramsApiGet = Summary " Recompute scores for ngrams table"
1300 :> QueryParamR "ngramsType" TabType
1301 :> QueryParamR "list" ListId
1302 :> "recompute" :> Post '[JSON] Int
1304 type TableNgramsApiGetVersion = Summary " Table Ngrams API Get Version"
1305 :> QueryParamR "ngramsType" TabType
1306 :> QueryParamR "list" ListId
1307 :> Get '[JSON] Version
1309 type TableNgramsApi = TableNgramsApiGet
1310 :<|> TableNgramsApiPut
1311 :<|> RecomputeScoresNgramsApiGet
1312 :<|> "version" :> TableNgramsApiGetVersion
1314 getTableNgramsCorpus :: (RepoCmdM env err m, HasNodeError err, HasConnectionPool env, HasConfig env)
1321 -> Maybe MinSize -> Maybe MaxSize
1323 -> Maybe Text -- full text search
1324 -> m (Versioned NgramsTable)
1325 getTableNgramsCorpus nId tabType listId limit_ offset listType minSize maxSize orderBy mt =
1326 getTableNgrams NodeCorpus nId tabType listId limit_ offset listType minSize maxSize orderBy searchQuery
1328 searchQuery (NgramsTerm nt) = maybe (const True) isInfixOf mt nt
1330 getTableNgramsVersion :: (RepoCmdM env err m, HasNodeError err, HasConnectionPool env, HasConfig env)
1335 getTableNgramsVersion _nId _tabType _listId = currentVersion
1337 -- Versioned { _v_version = v } <- getTableNgramsCorpus nId tabType listId 100000 Nothing Nothing Nothing Nothing Nothing Nothing
1338 -- This line above looks like a waste of computation to finally get only the version.
1339 -- See the comment about listNgramsChangedSince.
1342 -- | Text search is deactivated for now for ngrams by doc only
1343 getTableNgramsDoc :: (RepoCmdM env err m, HasNodeError err, HasConnectionPool env, HasConfig env)
1345 -> ListId -> Limit -> Maybe Offset
1347 -> Maybe MinSize -> Maybe MaxSize
1349 -> Maybe Text -- full text search
1350 -> m (Versioned NgramsTable)
1351 getTableNgramsDoc dId tabType listId limit_ offset listType minSize maxSize orderBy _mt = do
1352 ns <- selectNodesWithUsername NodeList userMaster
1353 let ngramsType = ngramsTypeFromTabType tabType
1354 ngs <- selectNgramsByDoc (ns <> [listId]) dId ngramsType
1355 let searchQuery (NgramsTerm nt) = flip S.member (S.fromList ngs) nt
1356 getTableNgrams NodeDocument dId tabType listId limit_ offset listType minSize maxSize orderBy searchQuery
1360 apiNgramsTableCorpus :: ( RepoCmdM env err m
1362 , HasInvalidError err
1363 , HasConnectionPool env
1366 => NodeId -> ServerT TableNgramsApi m
1367 apiNgramsTableCorpus cId = getTableNgramsCorpus cId
1369 :<|> scoresRecomputeTableNgrams cId
1370 :<|> getTableNgramsVersion cId
1372 apiNgramsTableDoc :: ( RepoCmdM env err m
1374 , HasInvalidError err
1375 , HasConnectionPool env
1378 => DocId -> ServerT TableNgramsApi m
1379 apiNgramsTableDoc dId = getTableNgramsDoc dId
1381 :<|> scoresRecomputeTableNgrams dId
1382 :<|> getTableNgramsVersion dId
1383 -- > index all the corpus accordingly (TODO AD)
1385 -- Did the given list of ngrams changed since the given version?
1386 -- The returned value is versioned boolean value, meaning that one always retrieve the
1388 -- If the given version is negative then one simply receive the latest version and True.
1389 -- Using this function is more precise than simply comparing the latest version number
1390 -- with the local version number. Indeed there might be no change to this particular list
1391 -- and still the version number has changed because of other lists.
1393 -- Here the added value is to make a compromise between precision, computation, and bandwidth:
1394 -- * currentVersion: good computation, good bandwidth, bad precision.
1395 -- * listNgramsChangedSince: good precision, good bandwidth, bad computation.
1396 -- * tableNgramsPull: good precision, good bandwidth (if you use the received data!), bad computation.
1397 listNgramsChangedSince :: RepoCmdM env err m
1398 => ListId -> TableNgrams.NgramsType -> Version -> m (Versioned Bool)
1399 listNgramsChangedSince listId ngramsType version
1401 Versioned <$> currentVersion <*> pure True
1403 tableNgramsPull listId ngramsType version & mapped . v_data %~ (== mempty)
1406 instance Arbitrary NgramsRepoElement where
1407 arbitrary = elements $ map ngramsElementToRepo ns
1409 NgramsTable ns = mockTable
1412 instance FromHttpApiData (Map TableNgrams.NgramsType (Versioned NgramsTableMap))
1414 parseUrlPiece x = maybeToEither x (decode $ cs x)