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 {-# LANGUAGE ConstraintKinds #-}
19 {-# LANGUAGE DataKinds #-}
20 {-# LANGUAGE DeriveGeneric #-}
21 {-# LANGUAGE NoImplicitPrelude #-}
22 {-# LANGUAGE OverloadedStrings #-}
23 {-# LANGUAGE ScopedTypeVariables #-}
24 {-# LANGUAGE TemplateHaskell #-}
25 {-# LANGUAGE TypeOperators #-}
26 {-# LANGUAGE FlexibleContexts #-}
27 {-# LANGUAGE FlexibleInstances #-}
28 {-# LANGUAGE GeneralizedNewtypeDeriving #-}
29 {-# LANGUAGE MultiParamTypeClasses #-}
30 {-# LANGUAGE RankNTypes #-}
31 {-# LANGUAGE TypeFamilies #-}
32 {-# OPTIONS -fno-warn-orphans #-}
34 module Gargantext.API.Ngrams
37 -- import Debug.Trace (trace)
38 import Prelude (Enum, Bounded, Semigroup(..), minBound, maxBound {-, round-}, error)
39 -- import Gargantext.Database.Schema.User (UserId)
40 import Data.Patch.Class (Replace, replace, Action(act), Applicable(..),
41 Composable(..), Transformable(..),
42 PairPatch(..), Patched, ConflictResolution,
43 ConflictResolutionReplace, ours)
44 import qualified Data.Map.Strict.Patch as PM
46 import Data.Ord (Down(..))
48 --import Data.Semigroup
50 import qualified Data.Set as S
51 import qualified Data.List as List
52 import Data.Maybe (fromMaybe)
53 -- import Data.Tuple.Extra (first)
54 import qualified Data.Map.Strict as Map
55 import Data.Map.Strict (Map)
56 import qualified Data.Set as Set
57 import Control.Category ((>>>))
58 import Control.Concurrent
59 import Control.Lens (makeLenses, makePrisms, Getter, Iso', iso, from, (.~), (?=), (#), to, folded, {-withIndex, ifolded,-} view, use, (^.), (^..), (^?), (+~), (%~), (%=), sumOf, at, _Just, Each(..), itraverse_, both, forOf_)
60 import Control.Monad.Error.Class (MonadError)
61 import Control.Monad.Reader
62 import Control.Monad.State
63 import Data.Aeson hiding ((.=))
64 import Data.Aeson.TH (deriveJSON)
65 import Data.Either(Either(Left))
66 -- import Data.Map (lookup)
67 import qualified Data.HashMap.Strict.InsOrd as InsOrdHashMap
68 import Data.Swagger hiding (version, patch)
69 import Data.Text (Text, isInfixOf, count)
71 import GHC.Generics (Generic)
72 import Gargantext.Core.Utils.Prefix (unPrefix)
73 -- import Gargantext.Database.Schema.Ngrams (NgramsTypeId, ngramsTypeId, NgramsTableData(..))
74 import Gargantext.Database.Config (userMaster)
75 import Gargantext.Database.Metrics.NgramsByNode (getOccByNgramsOnlySafe)
76 import Gargantext.Database.Schema.Ngrams (NgramsType)
77 import Gargantext.Database.Types.Node (NodeType(..))
78 import Gargantext.Database.Utils (fromField', HasConnection)
79 import Gargantext.Database.Node.Select
80 import Gargantext.Database.Ngrams
81 --import Gargantext.Database.Lists (listsWith)
82 import Gargantext.Database.Schema.Node (HasNodeError)
83 import Database.PostgreSQL.Simple.FromField (FromField, fromField)
84 import qualified Gargantext.Database.Schema.Ngrams as Ngrams
85 -- import Gargantext.Database.Schema.NodeNgram hiding (Action)
86 import Gargantext.Prelude
87 -- import Gargantext.Core.Types (ListTypeId, listTypeId)
88 import Gargantext.Core.Types (ListType(..), NodeId, ListId, DocId, Limit, Offset, HasInvalidError, assertValid)
89 import Servant hiding (Patch)
90 import System.FileLock (FileLock)
91 import Test.QuickCheck (elements)
92 import Test.QuickCheck.Arbitrary (Arbitrary, arbitrary)
97 instance ToSchema TODO where
99 ------------------------------------------------------------------------
100 --data FacetFormat = Table | Chart
101 data TabType = Docs | Terms | Sources | Authors | Institutes | Trash
103 deriving (Generic, Enum, Bounded)
105 instance FromHttpApiData TabType
107 parseUrlPiece "Docs" = pure Docs
108 parseUrlPiece "Terms" = pure Terms
109 parseUrlPiece "Sources" = pure Sources
110 parseUrlPiece "Institutes" = pure Institutes
111 parseUrlPiece "Authors" = pure Authors
112 parseUrlPiece "Trash" = pure Trash
114 parseUrlPiece "Contacts" = pure Contacts
116 parseUrlPiece _ = Left "Unexpected value of TabType"
118 instance ToParamSchema TabType
119 instance ToJSON TabType
120 instance FromJSON TabType
121 instance ToSchema TabType
122 instance Arbitrary TabType
124 arbitrary = elements [minBound .. maxBound]
126 newtype MSet a = MSet (Map a ())
127 deriving (Eq, Ord, Show, Generic, Arbitrary, Semigroup, Monoid)
129 instance ToJSON a => ToJSON (MSet a) where
130 toJSON (MSet m) = toJSON (Map.keys m)
131 toEncoding (MSet m) = toEncoding (Map.keys m)
133 mSetFromSet :: Set a -> MSet a
134 mSetFromSet = MSet . Map.fromSet (const ())
136 mSetFromList :: Ord a => [a] -> MSet a
137 mSetFromList = MSet . Map.fromList . map (\x -> (x, ()))
139 -- mSetToSet :: Ord a => MSet a -> Set a
140 -- mSetToSet (MSet a) = Set.fromList ( Map.keys a)
141 mSetToSet :: Ord a => MSet a -> Set a
142 mSetToSet = Set.fromList . mSetToList
144 mSetToList :: MSet a -> [a]
145 mSetToList (MSet a) = Map.keys a
147 instance Foldable MSet where
148 foldMap f (MSet m) = Map.foldMapWithKey (\k _ -> f k) m
150 instance (Ord a, FromJSON a) => FromJSON (MSet a) where
151 parseJSON = fmap mSetFromList . parseJSON
153 instance (ToJSONKey a, ToSchema a) => ToSchema (MSet a) where
155 declareNamedSchema _ = declareNamedSchema (Proxy :: Proxy TODO)
157 ------------------------------------------------------------------------
158 type NgramsTerm = Text
160 data RootParent = RootParent
161 { _rp_root :: NgramsTerm
162 , _rp_parent :: NgramsTerm
164 deriving (Ord, Eq, Show, Generic)
166 deriveJSON (unPrefix "_rp_") ''RootParent
167 makeLenses ''RootParent
169 data NgramsRepoElement = NgramsRepoElement
171 , _nre_list :: ListType
172 --, _nre_root_parent :: Maybe RootParent
173 , _nre_root :: Maybe NgramsTerm
174 , _nre_parent :: Maybe NgramsTerm
175 , _nre_children :: MSet NgramsTerm
177 deriving (Ord, Eq, Show, Generic)
179 deriveJSON (unPrefix "_nre_") ''NgramsRepoElement
180 makeLenses ''NgramsRepoElement
183 NgramsElement { _ne_ngrams :: NgramsTerm
185 , _ne_list :: ListType
186 , _ne_occurrences :: Int
187 , _ne_root :: Maybe NgramsTerm
188 , _ne_parent :: Maybe NgramsTerm
189 , _ne_children :: MSet NgramsTerm
191 deriving (Ord, Eq, Show, Generic)
193 deriveJSON (unPrefix "_ne_") ''NgramsElement
194 makeLenses ''NgramsElement
196 mkNgramsElement :: NgramsTerm -> ListType -> Maybe RootParent -> MSet NgramsTerm -> NgramsElement
197 mkNgramsElement ngrams list rp children =
198 NgramsElement ngrams size list 1 (_rp_root <$> rp) (_rp_parent <$> rp) children
201 size = 1 + count " " ngrams
203 instance ToSchema NgramsElement
204 instance Arbitrary NgramsElement where
205 arbitrary = elements [mkNgramsElement "sport" GraphTerm Nothing mempty]
207 ngramsElementToRepo :: NgramsElement -> NgramsRepoElement
209 (NgramsElement { _ne_size = s
223 ngramsElementFromRepo :: (NgramsTerm, NgramsRepoElement) -> NgramsElement
224 ngramsElementFromRepo
233 NgramsElement { _ne_size = s
238 , _ne_ngrams = ngrams
239 , _ne_occurrences = panic "API.Ngrams._ne_occurrences"
241 -- Here we could use 0 if we want to avoid any `panic`.
242 -- It will not happen using getTableNgrams if
243 -- getOccByNgramsOnly provides a count of occurrences for
244 -- all the ngrams given.
248 ------------------------------------------------------------------------
249 newtype NgramsTable = NgramsTable [NgramsElement]
250 deriving (Ord, Eq, Generic, ToJSON, FromJSON, Show)
252 type ListNgrams = NgramsTable
254 makePrisms ''NgramsTable
256 -- | Question: why these repetition of Type in this instance
257 -- may you document it please ?
258 instance Each NgramsTable NgramsTable NgramsElement NgramsElement where
259 each = _NgramsTable . each
262 -- | TODO Check N and Weight
264 toNgramsElement :: [NgramsTableData] -> [NgramsElement]
265 toNgramsElement ns = map toNgramsElement' ns
267 toNgramsElement' (NgramsTableData _ p t _ lt w) = NgramsElement t lt' (round w) p' c'
271 Just x -> lookup x mapParent
272 c' = maybe mempty identity $ lookup t mapChildren
273 lt' = maybe (panic "API.Ngrams: listypeId") identity lt
275 mapParent :: Map Int Text
276 mapParent = Map.fromListWith (<>) $ map (\(NgramsTableData i _ t _ _ _) -> (i,t)) ns
278 mapChildren :: Map Text (Set Text)
279 mapChildren = Map.mapKeys (\i -> (maybe (panic "API.Ngrams.mapChildren: ParentId with no Terms: Impossible") identity $ lookup i mapParent))
280 $ Map.fromListWith (<>)
281 $ map (first fromJust)
282 $ filter (isJust . fst)
283 $ map (\(NgramsTableData _ p t _ _ _) -> (p, Set.singleton t)) ns
286 mockTable :: NgramsTable
287 mockTable = NgramsTable
288 [ mkNgramsElement "animal" GraphTerm Nothing (mSetFromList ["dog", "cat"])
289 , mkNgramsElement "cat" GraphTerm (rp "animal") mempty
290 , mkNgramsElement "cats" StopTerm Nothing mempty
291 , mkNgramsElement "dog" GraphTerm (rp "animal") (mSetFromList ["dogs"])
292 , mkNgramsElement "dogs" StopTerm (rp "dog") mempty
293 , mkNgramsElement "fox" GraphTerm Nothing mempty
294 , mkNgramsElement "object" CandidateTerm Nothing mempty
295 , mkNgramsElement "nothing" StopTerm Nothing mempty
296 , mkNgramsElement "organic" GraphTerm Nothing (mSetFromList ["flower"])
297 , mkNgramsElement "flower" GraphTerm (rp "organic") mempty
298 , mkNgramsElement "moon" CandidateTerm Nothing mempty
299 , mkNgramsElement "sky" StopTerm Nothing mempty
302 rp n = Just $ RootParent n n
304 instance Arbitrary NgramsTable where
305 arbitrary = pure mockTable
307 instance ToSchema NgramsTable
309 ------------------------------------------------------------------------
310 type NgramsTableMap = Map NgramsTerm NgramsRepoElement
312 ------------------------------------------------------------------------
313 -- On the Client side:
314 --data Action = InGroup NgramsId NgramsId
315 -- | OutGroup NgramsId NgramsId
316 -- | SetListType NgramsId ListType
318 data PatchSet a = PatchSet
322 deriving (Eq, Ord, Show, Generic)
324 makeLenses ''PatchSet
325 makePrisms ''PatchSet
327 instance ToJSON a => ToJSON (PatchSet a) where
328 toJSON = genericToJSON $ unPrefix "_"
329 toEncoding = genericToEncoding $ unPrefix "_"
331 instance (Ord a, FromJSON a) => FromJSON (PatchSet a) where
332 parseJSON = genericParseJSON $ unPrefix "_"
335 instance (Ord a, Arbitrary a) => Arbitrary (PatchSet a) where
336 arbitrary = PatchSet <$> arbitrary <*> arbitrary
338 type instance Patched (PatchSet a) = Set a
340 type ConflictResolutionPatchSet a = SimpleConflictResolution' (Set a)
341 type instance ConflictResolution (PatchSet a) = ConflictResolutionPatchSet a
343 instance Ord a => Semigroup (PatchSet a) where
344 p <> q = PatchSet { _rem = (q ^. rem) `Set.difference` (p ^. add) <> p ^. rem
345 , _add = (q ^. add) `Set.difference` (p ^. rem) <> p ^. add
348 instance Ord a => Monoid (PatchSet a) where
349 mempty = PatchSet mempty mempty
351 instance Ord a => Group (PatchSet a) where
352 invert (PatchSet r a) = PatchSet a r
354 instance Ord a => Composable (PatchSet a) where
355 composable _ _ = undefined
357 instance Ord a => Action (PatchSet a) (Set a) where
358 act p source = (source `Set.difference` (p ^. rem)) <> p ^. add
360 instance Applicable (PatchSet a) (Set a) where
361 applicable _ _ = mempty
363 instance Ord a => Validity (PatchSet a) where
364 validate p = check (Set.disjoint (p ^. rem) (p ^. add)) "_rem and _add should be dijoint"
366 instance Ord a => Transformable (PatchSet a) where
367 transformable = undefined
369 conflicts _p _q = undefined
371 transformWith conflict p q = undefined conflict p q
373 instance ToSchema a => ToSchema (PatchSet a)
376 type AddRem = Replace (Maybe ())
378 remPatch, addPatch :: AddRem
379 remPatch = replace (Just ()) Nothing
380 addPatch = replace Nothing (Just ())
382 isRem :: Replace (Maybe ()) -> Bool
383 isRem = (== remPatch)
385 type PatchMap = PM.PatchMap
387 newtype PatchMSet a = PatchMSet (PatchMap a AddRem)
388 deriving (Eq, Show, Generic, Validity, Semigroup, Monoid,
389 Transformable, Composable)
391 type ConflictResolutionPatchMSet a = a -> ConflictResolutionReplace (Maybe ())
392 type instance ConflictResolution (PatchMSet a) = ConflictResolutionPatchMSet a
394 -- TODO this breaks module abstraction
395 makePrisms ''PM.PatchMap
397 makePrisms ''PatchMSet
399 _PatchMSetIso :: Ord a => Iso' (PatchMSet a) (PatchSet a)
400 _PatchMSetIso = _PatchMSet . _PatchMap . iso f g . from _PatchSet
402 f :: Ord a => Map a (Replace (Maybe ())) -> (Set a, Set a)
403 f = Map.partition isRem >>> both %~ Map.keysSet
405 g :: Ord a => (Set a, Set a) -> Map a (Replace (Maybe ()))
406 g (rems, adds) = Map.fromSet (const remPatch) rems
407 <> Map.fromSet (const addPatch) adds
409 instance Ord a => Action (PatchMSet a) (MSet a) where
410 act (PatchMSet p) (MSet m) = MSet $ act p m
412 instance Ord a => Applicable (PatchMSet a) (MSet a) where
413 applicable (PatchMSet p) (MSet m) = applicable p m
415 instance (Ord a, ToJSON a) => ToJSON (PatchMSet a) where
416 toJSON = toJSON . view _PatchMSetIso
417 toEncoding = toEncoding . view _PatchMSetIso
419 instance (Ord a, FromJSON a) => FromJSON (PatchMSet a) where
420 parseJSON = fmap (_PatchMSetIso #) . parseJSON
422 instance (Ord a, Arbitrary a) => Arbitrary (PatchMSet a) where
423 arbitrary = (PatchMSet . PM.fromMap) <$> arbitrary
425 instance ToSchema a => ToSchema (PatchMSet a) where
427 declareNamedSchema _ = declareNamedSchema (Proxy :: Proxy TODO)
429 type instance Patched (PatchMSet a) = MSet a
431 instance (Eq a, Arbitrary a) => Arbitrary (Replace a) where
432 arbitrary = uncurry replace <$> arbitrary
433 -- If they happen to be equal then the patch is Keep.
435 instance ToSchema a => ToSchema (Replace a) where
436 declareNamedSchema (_ :: proxy (Replace a)) = do
437 -- TODO Keep constructor is not supported here.
438 aSchema <- declareSchemaRef (Proxy :: Proxy a)
439 return $ NamedSchema (Just "Replace") $ mempty
440 & type_ .~ SwaggerObject
442 InsOrdHashMap.fromList
446 & required .~ [ "old", "new" ]
449 NgramsPatch { _patch_children :: PatchMSet NgramsTerm
450 , _patch_list :: Replace ListType -- TODO Map UserId ListType
452 deriving (Eq, Show, Generic)
454 deriveJSON (unPrefix "_") ''NgramsPatch
455 makeLenses ''NgramsPatch
457 instance ToSchema NgramsPatch
459 instance Arbitrary NgramsPatch where
460 arbitrary = NgramsPatch <$> arbitrary <*> (replace <$> arbitrary <*> arbitrary)
462 type NgramsPatchIso = PairPatch (PatchMSet NgramsTerm) (Replace ListType)
464 _NgramsPatch :: Iso' NgramsPatch NgramsPatchIso
465 _NgramsPatch = iso (\(NgramsPatch c l) -> c :*: l) (\(c :*: l) -> NgramsPatch c l)
467 instance Semigroup NgramsPatch where
468 p <> q = _NgramsPatch # (p ^. _NgramsPatch <> q ^. _NgramsPatch)
470 instance Monoid NgramsPatch where
471 mempty = _NgramsPatch # mempty
473 instance Validity NgramsPatch where
474 validate p = p ^. _NgramsPatch . to validate
476 instance Transformable NgramsPatch where
477 transformable p q = transformable (p ^. _NgramsPatch) (q ^. _NgramsPatch)
479 conflicts p q = conflicts (p ^. _NgramsPatch) (q ^. _NgramsPatch)
481 transformWith conflict p q = (_NgramsPatch # p', _NgramsPatch # q')
483 (p', q') = transformWith conflict (p ^. _NgramsPatch) (q ^. _NgramsPatch)
485 type ConflictResolutionNgramsPatch =
486 ( ConflictResolutionPatchMSet NgramsTerm
487 , ConflictResolutionReplace ListType
489 type instance ConflictResolution NgramsPatch =
490 ConflictResolutionNgramsPatch
492 type PatchedNgramsPatch = (Set NgramsTerm, ListType)
493 -- ~ Patched NgramsPatchIso
494 type instance Patched NgramsPatch = PatchedNgramsPatch
496 instance Applicable NgramsPatch (Maybe NgramsRepoElement) where
497 applicable p Nothing = check (p == mempty) "NgramsPatch should be empty here"
498 applicable p (Just nre) =
499 applicable (p ^. patch_children) (nre ^. nre_children) <>
500 applicable (p ^. patch_list) (nre ^. nre_list)
502 instance Action NgramsPatch NgramsRepoElement where
503 act p = (nre_children %~ act (p ^. patch_children))
504 . (nre_list %~ act (p ^. patch_list))
506 instance Action NgramsPatch (Maybe NgramsRepoElement) where
509 newtype NgramsTablePatch = NgramsTablePatch (PatchMap NgramsTerm NgramsPatch)
510 deriving (Eq, Show, Generic, ToJSON, FromJSON, Semigroup, Monoid, Validity, Transformable)
512 instance FromField NgramsTablePatch
514 fromField = fromField'
516 instance FromField (PatchMap NgramsType (PatchMap NodeId NgramsTablePatch))
518 fromField = fromField'
520 --instance (Ord k, Action pv (Maybe v)) => Action (PatchMap k pv) (Map k v) where
522 type instance ConflictResolution NgramsTablePatch =
523 NgramsTerm -> ConflictResolutionNgramsPatch
525 type PatchedNgramsTablePatch = Map NgramsTerm PatchedNgramsPatch
526 -- ~ Patched (PatchMap NgramsTerm NgramsPatch)
527 type instance Patched NgramsTablePatch = PatchedNgramsTablePatch
529 makePrisms ''NgramsTablePatch
530 instance ToSchema (PatchMap NgramsTerm NgramsPatch)
531 instance ToSchema NgramsTablePatch
533 instance Applicable NgramsTablePatch (Maybe NgramsTableMap) where
534 applicable p = applicable (p ^. _NgramsTablePatch)
536 instance Action NgramsTablePatch (Maybe NgramsTableMap) where
538 fmap (execState (reParentNgramsTablePatch p)) .
539 act (p ^. _NgramsTablePatch)
541 instance Arbitrary NgramsTablePatch where
542 arbitrary = NgramsTablePatch <$> PM.fromMap <$> arbitrary
544 -- Should it be less than an Lens' to preserve PatchMap's abstraction.
545 -- ntp_ngrams_patches :: Lens' NgramsTablePatch (Map NgramsTerm NgramsPatch)
546 -- ntp_ngrams_patches = _NgramsTablePatch . undefined
548 type ReParent a = forall m. MonadState NgramsTableMap m => a -> m ()
550 reRootChildren :: NgramsTerm -> ReParent NgramsTerm
551 reRootChildren root ngram = do
552 nre <- use $ at ngram
553 forOf_ (_Just . nre_children . folded) nre $ \child -> do
554 at child . _Just . nre_root ?= root
555 reRootChildren root child
557 reParent :: Maybe RootParent -> ReParent NgramsTerm
558 reParent rp child = do
559 at child . _Just %= ( (nre_parent .~ (_rp_parent <$> rp))
560 . (nre_root .~ (_rp_root <$> rp))
562 reRootChildren (fromMaybe child (rp ^? _Just . rp_root)) child
564 reParentAddRem :: RootParent -> NgramsTerm -> ReParent AddRem
565 reParentAddRem rp child p =
566 reParent (if isRem p then Nothing else Just rp) child
568 reParentNgramsPatch :: NgramsTerm -> ReParent NgramsPatch
569 reParentNgramsPatch parent ngramsPatch = do
570 root_of_parent <- use (at parent . _Just . nre_root)
572 root = fromMaybe parent root_of_parent
573 rp = RootParent { _rp_root = root, _rp_parent = parent }
574 itraverse_ (reParentAddRem rp) (ngramsPatch ^. patch_children . _PatchMSet . _PatchMap)
575 -- TODO FoldableWithIndex/TraversableWithIndex for PatchMap
577 reParentNgramsTablePatch :: ReParent NgramsTablePatch
578 reParentNgramsTablePatch p = itraverse_ reParentNgramsPatch (p ^. _NgramsTablePatch. _PatchMap)
579 -- TODO FoldableWithIndex/TraversableWithIndex for PatchMap
581 ------------------------------------------------------------------------
582 ------------------------------------------------------------------------
585 data Versioned a = Versioned
586 { _v_version :: Version
589 deriving (Generic, Show)
590 deriveJSON (unPrefix "_v_") ''Versioned
591 makeLenses ''Versioned
592 instance ToSchema a => ToSchema (Versioned a)
593 instance Arbitrary a => Arbitrary (Versioned a) where
594 arbitrary = Versioned 1 <$> arbitrary -- TODO 1 is constant so far
597 -- TODO sequencs of modifications (Patchs)
598 type NgramsIdPatch = Patch NgramsId NgramsPatch
600 ngramsPatch :: Int -> NgramsPatch
601 ngramsPatch n = NgramsPatch (DM.fromList [(1, StopTerm)]) (Set.fromList [n]) Set.empty
603 toEdit :: NgramsId -> NgramsPatch -> Edit NgramsId NgramsPatch
604 toEdit n p = Edit n p
605 ngramsIdPatch :: Patch NgramsId NgramsPatch
606 ngramsIdPatch = fromList $ catMaybes $ reverse [ replace (1::NgramsId) (Just $ ngramsPatch 1) Nothing
607 , replace (1::NgramsId) Nothing (Just $ ngramsPatch 2)
608 , replace (2::NgramsId) Nothing (Just $ ngramsPatch 2)
611 -- applyPatchBack :: Patch -> IO Patch
612 -- isEmptyPatch = Map.all (\x -> Set.isEmpty (add_children x) && Set.isEmpty ... )
614 ------------------------------------------------------------------------
615 ------------------------------------------------------------------------
616 ------------------------------------------------------------------------
619 -- TODO: Replace.old is ignored which means that if the current list
620 -- `GraphTerm` and that the patch is `Replace CandidateTerm StopTerm` then
621 -- the list is going to be `StopTerm` while it should keep `GraphTerm`.
622 -- However this should not happen in non conflicting situations.
623 mkListsUpdate :: NgramsType -> NgramsTablePatch -> [(NgramsTypeId, NgramsTerm, ListTypeId)]
624 mkListsUpdate nt patches =
625 [ (ngramsTypeId nt, ng, listTypeId lt)
626 | (ng, patch) <- patches ^.. ntp_ngrams_patches . ifolded . withIndex
627 , lt <- patch ^.. patch_list . new
630 mkChildrenGroups :: (PatchSet NgramsTerm -> Set NgramsTerm)
633 -> [(NgramsTypeId, NgramsParent, NgramsChild)]
634 mkChildrenGroups addOrRem nt patches =
635 [ (ngramsTypeId nt, parent, child)
636 | (parent, patch) <- patches ^.. ntp_ngrams_patches . ifolded . withIndex
637 , child <- patch ^.. patch_children . to addOrRem . folded
641 ngramsTypeFromTabType :: TabType -> NgramsType
642 ngramsTypeFromTabType tabType =
643 let lieu = "Garg.API.Ngrams: " :: Text in
645 Sources -> Ngrams.Sources
646 Authors -> Ngrams.Authors
647 Institutes -> Ngrams.Institutes
648 Terms -> Ngrams.NgramsTerms
649 _ -> panic $ lieu <> "No Ngrams for this tab"
650 -- TODO: This `panic` would disapear with custom NgramsType.
652 ------------------------------------------------------------------------
654 { _r_version :: Version
657 -- first patch in the list is the most recent
661 instance (FromJSON s, FromJSON p) => FromJSON (Repo s p) where
662 parseJSON = genericParseJSON $ unPrefix "_r_"
664 instance (ToJSON s, ToJSON p) => ToJSON (Repo s p) where
665 toJSON = genericToJSON $ unPrefix "_r_"
666 toEncoding = genericToEncoding $ unPrefix "_r_"
670 initRepo :: Monoid s => Repo s p
671 initRepo = Repo 1 mempty []
673 type NgramsRepo = Repo NgramsState NgramsStatePatch
674 type NgramsState = Map NgramsType (Map NodeId NgramsTableMap)
675 type NgramsStatePatch = PatchMap NgramsType (PatchMap NodeId NgramsTablePatch)
677 initMockRepo :: NgramsRepo
678 initMockRepo = Repo 1 s []
680 s = Map.singleton Ngrams.NgramsTerms
681 $ Map.singleton 47254
683 [ (n ^. ne_ngrams, ngramsElementToRepo n) | n <- mockTable ^. _NgramsTable ]
685 data RepoEnv = RepoEnv
686 { _renv_var :: !(MVar NgramsRepo)
687 , _renv_saver :: !(IO ())
688 , _renv_lock :: !FileLock
694 class HasRepoVar env where
695 repoVar :: Getter env (MVar NgramsRepo)
697 instance HasRepoVar (MVar NgramsRepo) where
700 class HasRepoSaver env where
701 repoSaver :: Getter env (IO ())
703 class (HasRepoVar env, HasRepoSaver env) => HasRepo env where
704 repoEnv :: Getter env RepoEnv
706 instance HasRepo RepoEnv where
709 instance HasRepoVar RepoEnv where
712 instance HasRepoSaver RepoEnv where
713 repoSaver = renv_saver
715 type RepoCmdM env err m =
721 ------------------------------------------------------------------------
723 saveRepo :: ( MonadReader env m, MonadIO m, HasRepoSaver env )
725 saveRepo = liftIO =<< view repoSaver
727 listTypeConflictResolution :: ListType -> ListType -> ListType
728 listTypeConflictResolution _ _ = undefined -- TODO Use Map User ListType
730 ngramsStatePatchConflictResolution
731 :: NgramsType -> NodeId -> NgramsTerm
732 -> ConflictResolutionNgramsPatch
733 ngramsStatePatchConflictResolution _ngramsType _nodeId _ngramsTerm
735 -- undefined {- TODO think this through -}, listTypeConflictResolution)
738 -- Insertions are not considered as patches,
739 -- they do not extend history,
740 -- they do not bump version.
741 insertNewOnly :: a -> Maybe b -> a
742 insertNewOnly m = maybe m (const $ error "insertNewOnly: impossible")
743 -- TODO error handling
745 something :: Monoid a => Maybe a -> a
746 something Nothing = mempty
747 something (Just a) = a
750 -- TODO refactor with putListNgrams
751 copyListNgrams :: RepoCmdM env err m
752 => NodeId -> NodeId -> NgramsType
754 copyListNgrams srcListId dstListId ngramsType = do
756 liftIO $ modifyMVar_ var $
757 pure . (r_state . at ngramsType %~ (Just . f . something))
760 f :: Map NodeId NgramsTableMap -> Map NodeId NgramsTableMap
761 f m = m & at dstListId %~ insertNewOnly (m ^. at srcListId)
763 -- TODO refactor with putListNgrams
764 -- The list must be non-empty!
765 -- The added ngrams must be non-existent!
766 addListNgrams :: RepoCmdM env err m
767 => NodeId -> NgramsType
768 -> [NgramsElement] -> m ()
769 addListNgrams listId ngramsType nes = do
771 liftIO $ modifyMVar_ var $
772 pure . (r_state . at ngramsType . _Just . at listId . _Just <>~ m)
775 m = Map.fromList $ (\n -> (n ^. ne_ngrams, n)) <$> nes
778 -- If the given list of ngrams elements contains ngrams already in
779 -- the repo, they will overwrite the old ones.
780 putListNgrams :: RepoCmdM env err m
781 => NodeId -> NgramsType
782 -> [NgramsElement] -> m ()
783 putListNgrams _ _ [] = pure ()
784 putListNgrams listId ngramsType nes = do
785 -- printDebug "putListNgrams" (length nes)
787 liftIO $ modifyMVar_ var $
788 pure . (r_state . at ngramsType %~ (Just . (at listId %~ (Just . (m <>) . something)) . something))
791 m = Map.fromList $ (\n -> (n ^. ne_ngrams, ngramsElementToRepo n)) <$> nes
793 tableNgramsPost :: RepoCmdM env err m => TabType -> NodeId -> [NgramsElement] -> m ()
794 tableNgramsPost tabType listId = putListNgrams listId (ngramsTypeFromTabType tabType)
796 -- Apply the given patch to the DB and returns the patch to be applied on the
798 tableNgramsPut :: (HasInvalidError err, RepoCmdM env err m)
800 -> Versioned NgramsTablePatch
801 -> m (Versioned NgramsTablePatch)
802 tableNgramsPut tabType listId (Versioned p_version p_table)
803 | p_table == mempty = do
804 let ngramsType = ngramsTypeFromTabType tabType
807 r <- liftIO $ readMVar var
810 q = mconcat $ take (r ^. r_version - p_version) (r ^. r_history)
811 q_table = q ^. _PatchMap . at ngramsType . _Just . _PatchMap . at listId . _Just
813 pure (Versioned (r ^. r_version) q_table)
816 let ngramsType = ngramsTypeFromTabType tabType
817 (p0, p0_validity) = PM.singleton listId p_table
818 (p, p_validity) = PM.singleton ngramsType p0
820 assertValid p0_validity
821 assertValid p_validity
824 vq' <- liftIO $ modifyMVar var $ \r -> do
826 q = mconcat $ take (r ^. r_version - p_version) (r ^. r_history)
827 (p', q') = transformWith ngramsStatePatchConflictResolution p q
828 r' = r & r_version +~ 1
830 & r_history %~ (p' :)
831 q'_table = q' ^. _PatchMap . at ngramsType . _Just . _PatchMap . at listId . _Just
833 -- Ideally we would like to check these properties. However:
834 -- * They should be checked only to debug the code. The client data
835 -- should be able to trigger these.
836 -- * What kind of error should they throw (we are in IO here)?
837 -- * Should we keep modifyMVar?
838 -- * Should we throw the validation in an Exception, catch it around
839 -- modifyMVar and throw it back as an Error?
840 assertValid $ transformable p q
841 assertValid $ applicable p' (r ^. r_state)
843 pure (r', Versioned (r' ^. r_version) q'_table)
848 mergeNgramsElement :: NgramsRepoElement -> NgramsRepoElement -> NgramsRepoElement
849 mergeNgramsElement _neOld neNew = neNew
851 { _ne_list :: ListType
852 If we merge the parents/children we can potentially create cycles!
853 , _ne_parent :: Maybe NgramsTerm
854 , _ne_children :: MSet NgramsTerm
858 getNgramsTableMap :: RepoCmdM env err m
859 => NodeId -> NgramsType -> m (Versioned NgramsTableMap)
860 getNgramsTableMap nodeId ngramsType = do
862 repo <- liftIO $ readMVar v
863 pure $ Versioned (repo ^. r_version)
864 (repo ^. r_state . at ngramsType . _Just . at nodeId . _Just)
869 -- | TODO Errors management
870 -- TODO: polymorphic for Annuaire or Corpus or ...
871 -- | Table of Ngrams is a ListNgrams formatted (sorted and/or cut).
872 -- TODO: should take only one ListId
877 getTableNgrams :: (RepoCmdM env err m, HasNodeError err, HasConnection env)
879 -> ListId -> Limit -> Maybe Offset
881 -> Maybe MinSize -> Maybe MaxSize
883 -> (NgramsTerm -> Bool)
884 -> m (Versioned NgramsTable)
885 getTableNgrams nId tabType listId limit_ offset
886 listType minSize maxSize orderBy searchQuery = do
888 lIds <- selectNodesWithUsername NodeList userMaster
890 ngramsType = ngramsTypeFromTabType tabType
891 offset' = maybe 0 identity offset
892 listType' = maybe (const True) (==) listType
893 minSize' = maybe (const True) (<=) minSize
894 maxSize' = maybe (const True) (>=) maxSize
896 selected_node n = minSize' s
898 && searchQuery (n ^. ne_ngrams)
899 && listType' (n ^. ne_list)
903 selected_inner roots n = maybe False (`Set.member` roots) (n ^. ne_root)
905 sortOnOrder Nothing = identity
906 sortOnOrder (Just TermAsc) = List.sortOn $ view ne_ngrams
907 sortOnOrder (Just TermDesc) = List.sortOn $ Down . view ne_ngrams
908 sortOnOrder (Just ScoreAsc) = List.sortOn $ view ne_occurrences
909 sortOnOrder (Just ScoreDesc) = List.sortOn $ Down . view ne_occurrences
911 selectAndPaginate tableMap (NgramsTable list) = NgramsTable $ roots <> inners
913 rootOf ne = maybe ne (\r -> ngramsElementFromRepo (r, fromMaybe (panic "getTableNgrams: invalid root") (tableMap ^. v_data . at r)))
915 selected_nodes = list & take limit_
917 . filter selected_node
918 . sortOnOrder orderBy
919 roots = rootOf <$> selected_nodes
920 rootsSet = Set.fromList (_ne_ngrams <$> roots)
921 inners = list & filter (selected_inner rootsSet)
923 setScores False table = pure table
924 setScores True table = do
925 occurrences <- getOccByNgramsOnlySafe nId (lIds <> [listId]) ngramsType (table ^.. v_data . _NgramsTable . each . ne_ngrams)
928 setOcc ne = ne & ne_occurrences .~ sumOf (at (ne ^. ne_ngrams) . _Just) occurrences
930 pure $ table & v_data . _NgramsTable . each %~ setOcc
932 -- lists <- catMaybes <$> listsWith userMaster
933 -- trace (show lists) $
934 -- getNgramsTableMap ({-lists <>-} listIds) ngramsType
936 tableMap <- getNgramsTableMap listId ngramsType
937 let nSco = needsScores orderBy
938 table <- tableMap & v_data %~ (NgramsTable . fmap ngramsElementFromRepo . Map.toList)
940 setScores (not nSco) $ table & v_data %~ selectAndPaginate tableMap
945 -- TODO: find a better place for the code above, All APIs stay here
946 type QueryParamR = QueryParam' '[Required, Strict]
949 data OrderBy = TermAsc | TermDesc | ScoreAsc | ScoreDesc
950 deriving (Generic, Enum, Bounded, Read, Show)
952 instance FromHttpApiData OrderBy
954 parseUrlPiece "TermAsc" = pure TermAsc
955 parseUrlPiece "TermDesc" = pure TermDesc
956 parseUrlPiece "ScoreAsc" = pure ScoreAsc
957 parseUrlPiece "ScoreDesc" = pure ScoreDesc
958 parseUrlPiece _ = Left "Unexpected value of OrderBy"
960 instance ToParamSchema OrderBy
961 instance FromJSON OrderBy
962 instance ToJSON OrderBy
963 instance ToSchema OrderBy
964 instance Arbitrary OrderBy
966 arbitrary = elements [minBound..maxBound]
968 needsScores :: Maybe OrderBy -> Bool
969 needsScores (Just ScoreAsc) = True
970 needsScores (Just ScoreDesc) = True
971 needsScores _ = False
973 type TableNgramsApiGet = Summary " Table Ngrams API Get"
974 :> QueryParamR "ngramsType" TabType
975 :> QueryParamR "list" ListId
976 :> QueryParamR "limit" Limit
977 :> QueryParam "offset" Offset
978 :> QueryParam "listType" ListType
979 :> QueryParam "minTermSize" MinSize
980 :> QueryParam "maxTermSize" MaxSize
981 :> QueryParam "orderBy" OrderBy
982 :> QueryParam "search" Text
983 :> Get '[JSON] (Versioned NgramsTable)
985 type TableNgramsApiPut = Summary " Table Ngrams API Change"
986 :> QueryParamR "ngramsType" TabType
987 :> QueryParamR "list" ListId
988 :> ReqBody '[JSON] (Versioned NgramsTablePatch)
989 :> Put '[JSON] (Versioned NgramsTablePatch)
991 type TableNgramsApiPost = Summary " Table Ngrams API Adds new ngrams"
992 :> QueryParamR "ngramsType" TabType
993 :> QueryParamR "list" ListId
994 :> ReqBody '[JSON] [NgramsElement]
997 getTableNgramsCorpus :: (RepoCmdM env err m, HasNodeError err, HasConnection env)
999 -> ListId -> Limit -> Maybe Offset
1001 -> Maybe MinSize -> Maybe MaxSize
1003 -> Maybe Text -- full text search
1004 -> m (Versioned NgramsTable)
1005 getTableNgramsCorpus nId tabType listId limit_ offset listType minSize maxSize orderBy mt =
1006 getTableNgrams nId tabType listId limit_ offset listType minSize maxSize orderBy searchQuery
1008 searchQuery = maybe (const True) isInfixOf mt
1010 -- | Text search is deactivated for now for ngrams by doc only
1011 getTableNgramsDoc :: (RepoCmdM env err m, HasNodeError err, HasConnection env)
1013 -> ListId -> Limit -> Maybe Offset
1015 -> Maybe MinSize -> Maybe MaxSize
1017 -> Maybe Text -- full text search
1018 -> m (Versioned NgramsTable)
1019 getTableNgramsDoc dId tabType listId limit_ offset listType minSize maxSize orderBy _mt = do
1020 ns <- selectNodesWithUsername NodeList userMaster
1021 let ngramsType = ngramsTypeFromTabType tabType
1022 ngs <- selectNgramsByDoc (ns <> [listId]) dId ngramsType
1023 let searchQuery = flip S.member (S.fromList ngs)
1024 getTableNgrams dId tabType listId limit_ offset listType minSize maxSize orderBy searchQuery
1030 -- TODO Doc Table Ngrams API
1031 type ApiNgramsTableDoc = TableNgramsApiGet
1032 :<|> TableNgramsApiPut
1033 :<|> TableNgramsApiPost
1035 apiNgramsTableDoc :: ( RepoCmdM env err m
1037 , HasInvalidError err
1040 => DocId -> ServerT ApiNgramsTableDoc m
1041 apiNgramsTableDoc dId = getTableNgramsDoc dId
1043 :<|> tableNgramsPost
1044 -- > add new ngrams in database (TODO AD)
1045 -- > index all the corpus accordingly (TODO AD)