3 {-# LANGUAGE ConstraintKinds #-}
4 {-# LANGUAGE ScopedTypeVariables #-}
5 {-# LANGUAGE TemplateHaskell #-}
6 {-# LANGUAGE TypeOperators #-}
7 {-# LANGUAGE TypeFamilies #-}
8 {-# OPTIONS -fno-warn-orphans #-}
10 module Gargantext.API.Ngrams.Types where
12 import Codec.Serialise (Serialise())
13 import Control.Category ((>>>))
14 import Control.Concurrent
15 import Control.Lens (makeLenses, makePrisms, Getter, Iso', iso, from, (.~), (?=), (#), to, folded, {-withIndex, ifolded,-} view, use, (^.), (^?), (%~), (.~), (%=), at, _Just, Each(..), itraverse_, both, forOf_, (?~))
16 import Control.Monad.Reader
17 import Control.Monad.State
18 import Data.Aeson hiding ((.=))
19 import Data.Aeson.TH (deriveJSON)
20 import Data.Either (Either(..))
22 import qualified Data.HashMap.Strict.InsOrd as InsOrdHashMap
23 import qualified Data.List as List
24 import Data.Map.Strict (Map)
25 import qualified Data.Map.Strict as Map
26 import qualified Data.Map.Strict.Patch as PM
27 import Data.Maybe (fromMaybe)
29 import Data.Patch.Class (Replace, replace, Action(act), Group, Applicable(..), Composable(..), Transformable(..),
30 PairPatch(..), Patched, ConflictResolution, ConflictResolutionReplace,
31 MaybePatch(Mod), unMod, old, new)
33 import qualified Data.Set as Set
34 import Data.String (IsString, fromString)
35 import Data.Swagger hiding (version, patch)
36 import Data.Text (Text, pack, strip)
38 import Database.PostgreSQL.Simple.FromField (FromField, fromField, ResultError(ConversionFailed), returnError)
39 import GHC.Generics (Generic)
40 import Servant hiding (Patch)
41 import Servant.Job.Utils (jsonOptions)
42 import System.FileLock (FileLock)
43 import Test.QuickCheck (elements, frequency)
44 import Test.QuickCheck.Arbitrary (Arbitrary, arbitrary)
46 import Protolude (maybeToEither)
47 import Gargantext.Prelude
49 import Gargantext.Core.Text (size)
50 import Gargantext.Core.Types (ListType(..), ListId, NodeId)
51 import Gargantext.Core.Types (TODO)
52 import Gargantext.Core.Utils.Prefix (unPrefix, unPrefixUntagged, unPrefixSwagger, wellNamedSchema)
53 import Gargantext.Database.Prelude (fromField', CmdM')
54 import qualified Gargantext.Database.Query.Table.Ngrams as TableNgrams
56 ------------------------------------------------------------------------
57 --data FacetFormat = Table | Chart
58 data TabType = Docs | Trash | MoreFav | MoreTrash
59 | Terms | Sources | Authors | Institutes
61 deriving (Bounded, Enum, Eq, Generic, Ord, Show)
63 instance FromHttpApiData TabType
65 parseUrlPiece "Docs" = pure Docs
66 parseUrlPiece "Trash" = pure Trash
67 parseUrlPiece "MoreFav" = pure MoreFav
68 parseUrlPiece "MoreTrash" = pure MoreTrash
70 parseUrlPiece "Terms" = pure Terms
71 parseUrlPiece "Sources" = pure Sources
72 parseUrlPiece "Institutes" = pure Institutes
73 parseUrlPiece "Authors" = pure Authors
75 parseUrlPiece "Contacts" = pure Contacts
77 parseUrlPiece _ = Left "Unexpected value of TabType"
78 instance ToParamSchema TabType
79 instance ToJSON TabType
80 instance FromJSON TabType
81 instance ToSchema TabType
82 instance Arbitrary TabType
84 arbitrary = elements [minBound .. maxBound]
85 instance FromJSONKey TabType where
86 fromJSONKey = genericFromJSONKey defaultJSONKeyOptions
87 instance ToJSONKey TabType where
88 toJSONKey = genericToJSONKey defaultJSONKeyOptions
90 newtype MSet a = MSet (Map a ())
91 deriving (Eq, Ord, Show, Generic, Arbitrary, Semigroup, Monoid)
93 instance ToJSON a => ToJSON (MSet a) where
94 toJSON (MSet m) = toJSON (Map.keys m)
95 toEncoding (MSet m) = toEncoding (Map.keys m)
97 mSetFromSet :: Set a -> MSet a
98 mSetFromSet = MSet . Map.fromSet (const ())
100 mSetFromList :: Ord a => [a] -> MSet a
101 mSetFromList = MSet . Map.fromList . map (\x -> (x, ()))
103 -- mSetToSet :: Ord a => MSet a -> Set a
104 -- mSetToSet (MSet a) = Set.fromList ( Map.keys a)
105 mSetToSet :: Ord a => MSet a -> Set a
106 mSetToSet = Set.fromList . mSetToList
108 mSetToList :: MSet a -> [a]
109 mSetToList (MSet a) = Map.keys a
111 instance Foldable MSet where
112 foldMap f (MSet m) = Map.foldMapWithKey (\k _ -> f k) m
114 instance (Ord a, FromJSON a) => FromJSON (MSet a) where
115 parseJSON = fmap mSetFromList . parseJSON
117 instance (ToJSONKey a, ToSchema a) => ToSchema (MSet a) where
119 declareNamedSchema _ = wellNamedSchema "" (Proxy :: Proxy TODO)
121 ------------------------------------------------------------------------
122 newtype NgramsTerm = NgramsTerm { unNgramsTerm :: Text }
123 deriving (Ord, Eq, Show, Generic, ToJSONKey, ToJSON, FromJSON, Semigroup, Arbitrary, Serialise, ToSchema)
125 instance FromJSONKey NgramsTerm where
126 fromJSONKey = FromJSONKeyTextParser $ \t -> pure $ NgramsTerm $ strip t
128 instance IsString NgramsTerm where
129 fromString s = NgramsTerm $ pack s
131 instance FromField NgramsTerm
133 fromField field mb = do
134 v <- fromField field mb
136 Success a -> pure $ NgramsTerm $ strip a
137 Error _err -> returnError ConversionFailed field
138 $ List.intercalate " " [ "cannot parse hyperdata for JSON: "
142 data RootParent = RootParent
143 { _rp_root :: NgramsTerm
144 , _rp_parent :: NgramsTerm
146 deriving (Ord, Eq, Show, Generic)
148 deriveJSON (unPrefix "_rp_") ''RootParent
149 makeLenses ''RootParent
151 data NgramsRepoElement = NgramsRepoElement
153 , _nre_list :: !ListType
154 , _nre_root :: !(Maybe NgramsTerm)
155 , _nre_parent :: !(Maybe NgramsTerm)
156 , _nre_children :: !(MSet NgramsTerm)
158 deriving (Ord, Eq, Show, Generic)
160 deriveJSON (unPrefix "_nre_") ''NgramsRepoElement
162 -- if ngrams & not size => size
165 makeLenses ''NgramsRepoElement
167 instance ToSchema NgramsRepoElement where
168 declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "_nre_")
170 instance Serialise (MSet NgramsTerm)
171 instance Serialise NgramsRepoElement
174 NgramsElement { _ne_ngrams :: NgramsTerm
176 , _ne_list :: ListType
177 , _ne_occurrences :: Int
178 , _ne_root :: Maybe NgramsTerm
179 , _ne_parent :: Maybe NgramsTerm
180 , _ne_children :: MSet NgramsTerm
182 deriving (Ord, Eq, Show, Generic)
184 deriveJSON (unPrefix "_ne_") ''NgramsElement
185 makeLenses ''NgramsElement
187 mkNgramsElement :: NgramsTerm
192 mkNgramsElement ngrams list rp children =
193 NgramsElement ngrams (size (unNgramsTerm ngrams)) list 1 (_rp_root <$> rp) (_rp_parent <$> rp) children
195 newNgramsElement :: Maybe ListType -> NgramsTerm -> NgramsElement
196 newNgramsElement mayList ngrams =
197 mkNgramsElement ngrams (fromMaybe MapTerm mayList) Nothing mempty
199 instance ToSchema NgramsElement where
200 declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "_ne_")
201 instance Arbitrary NgramsElement where
202 arbitrary = elements [newNgramsElement Nothing "sport"]
205 ------------------------------------------------------------------------
206 newtype NgramsTable = NgramsTable [NgramsElement]
207 deriving (Ord, Eq, Generic, ToJSON, FromJSON, Show)
209 type NgramsList = NgramsTable
211 makePrisms ''NgramsTable
213 -- | Question: why these repetition of Type in this instance
214 -- may you document it please ?
215 instance Each NgramsTable NgramsTable NgramsElement NgramsElement where
216 each = _NgramsTable . each
219 -- | TODO Check N and Weight
221 toNgramsElement :: [NgramsTableData] -> [NgramsElement]
222 toNgramsElement ns = map toNgramsElement' ns
224 toNgramsElement' (NgramsTableData _ p t _ lt w) = NgramsElement t lt' (round w) p' c'
228 Just x -> lookup x mapParent
229 c' = maybe mempty identity $ lookup t mapChildren
230 lt' = maybe (panic "API.Ngrams: listypeId") identity lt
232 mapParent :: Map Int Text
233 mapParent = Map.fromListWith (<>) $ map (\(NgramsTableData i _ t _ _ _) -> (i,t)) ns
235 mapChildren :: Map Text (Set Text)
236 mapChildren = Map.mapKeys (\i -> (maybe (panic "API.Ngrams.mapChildren: ParentId with no Terms: Impossible") identity $ lookup i mapParent))
237 $ Map.fromListWith (<>)
238 $ map (first fromJust)
239 $ filter (isJust . fst)
240 $ map (\(NgramsTableData _ p t _ _ _) -> (p, Set.singleton t)) ns
243 mockTable :: NgramsTable
244 mockTable = NgramsTable
245 [ mkNgramsElement "animal" MapTerm Nothing (mSetFromList ["dog", "cat"])
246 , mkNgramsElement "cat" MapTerm (rp "animal") mempty
247 , mkNgramsElement "cats" StopTerm Nothing mempty
248 , mkNgramsElement "dog" MapTerm (rp "animal") (mSetFromList ["dogs"])
249 , mkNgramsElement "dogs" StopTerm (rp "dog") mempty
250 , mkNgramsElement "fox" MapTerm Nothing mempty
251 , mkNgramsElement "object" CandidateTerm Nothing mempty
252 , mkNgramsElement "nothing" StopTerm Nothing mempty
253 , mkNgramsElement "organic" MapTerm Nothing (mSetFromList ["flower"])
254 , mkNgramsElement "flower" MapTerm (rp "organic") mempty
255 , mkNgramsElement "moon" CandidateTerm Nothing mempty
256 , mkNgramsElement "sky" StopTerm Nothing mempty
259 rp n = Just $ RootParent n n
261 instance Arbitrary NgramsTable where
262 arbitrary = pure mockTable
264 instance ToSchema NgramsTable
266 ------------------------------------------------------------------------
267 type NgramsTableMap = Map NgramsTerm NgramsRepoElement
268 ------------------------------------------------------------------------
269 -- On the Client side:
270 --data Action = InGroup NgramsId NgramsId
271 -- | OutGroup NgramsId NgramsId
272 -- | SetListType NgramsId ListType
274 data PatchSet a = PatchSet
278 deriving (Eq, Ord, Show, Generic)
280 makeLenses ''PatchSet
281 makePrisms ''PatchSet
283 instance ToJSON a => ToJSON (PatchSet a) where
284 toJSON = genericToJSON $ unPrefix "_"
285 toEncoding = genericToEncoding $ unPrefix "_"
287 instance (Ord a, FromJSON a) => FromJSON (PatchSet a) where
288 parseJSON = genericParseJSON $ unPrefix "_"
291 instance (Ord a, Arbitrary a) => Arbitrary (PatchSet a) where
292 arbitrary = PatchSet <$> arbitrary <*> arbitrary
294 type instance Patched (PatchSet a) = Set a
296 type ConflictResolutionPatchSet a = SimpleConflictResolution' (Set a)
297 type instance ConflictResolution (PatchSet a) = ConflictResolutionPatchSet a
299 instance Ord a => Semigroup (PatchSet a) where
300 p <> q = PatchSet { _rem = (q ^. rem) `Set.difference` (p ^. add) <> p ^. rem
301 , _add = (q ^. add) `Set.difference` (p ^. rem) <> p ^. add
304 instance Ord a => Monoid (PatchSet a) where
305 mempty = PatchSet mempty mempty
307 instance Ord a => Group (PatchSet a) where
308 invert (PatchSet r a) = PatchSet a r
310 instance Ord a => Composable (PatchSet a) where
311 composable _ _ = undefined
313 instance Ord a => Action (PatchSet a) (Set a) where
314 act p source = (source `Set.difference` (p ^. rem)) <> p ^. add
316 instance Applicable (PatchSet a) (Set a) where
317 applicable _ _ = mempty
319 instance Ord a => Validity (PatchSet a) where
320 validate p = check (Set.disjoint (p ^. rem) (p ^. add)) "_rem and _add should be dijoint"
322 instance Ord a => Transformable (PatchSet a) where
323 transformable = undefined
325 conflicts _p _q = undefined
327 transformWith conflict p q = undefined conflict p q
329 instance ToSchema a => ToSchema (PatchSet a)
332 type AddRem = Replace (Maybe ())
334 instance Serialise AddRem
336 remPatch, addPatch :: AddRem
337 remPatch = replace (Just ()) Nothing
338 addPatch = replace Nothing (Just ())
340 isRem :: Replace (Maybe ()) -> Bool
341 isRem = (== remPatch)
343 type PatchMap = PM.PatchMap
346 newtype PatchMSet a = PatchMSet (PatchMap a AddRem)
347 deriving (Eq, Show, Generic, Validity, Semigroup, Monoid, Group,
348 Transformable, Composable)
350 type ConflictResolutionPatchMSet a = a -> ConflictResolutionReplace (Maybe ())
351 type instance ConflictResolution (PatchMSet a) = ConflictResolutionPatchMSet a
353 instance (Serialise a, Ord a) => Serialise (PatchMap a AddRem)
354 instance (Serialise a, Ord a) => Serialise (PatchMSet a)
356 -- TODO this breaks module abstraction
357 makePrisms ''PM.PatchMap
359 makePrisms ''PatchMSet
361 _PatchMSetIso :: Ord a => Iso' (PatchMSet a) (PatchSet a)
362 _PatchMSetIso = _PatchMSet . _PatchMap . iso f g . from _PatchSet
364 f :: Ord a => Map a (Replace (Maybe ())) -> (Set a, Set a)
365 f = Map.partition isRem >>> both %~ Map.keysSet
367 g :: Ord a => (Set a, Set a) -> Map a (Replace (Maybe ()))
368 g (rems, adds) = Map.fromSet (const remPatch) rems
369 <> Map.fromSet (const addPatch) adds
371 instance Ord a => Action (PatchMSet a) (MSet a) where
372 act (PatchMSet p) (MSet m) = MSet $ act p m
374 instance Ord a => Applicable (PatchMSet a) (MSet a) where
375 applicable (PatchMSet p) (MSet m) = applicable p m
377 instance (Ord a, ToJSON a) => ToJSON (PatchMSet a) where
378 toJSON = toJSON . view _PatchMSetIso
379 toEncoding = toEncoding . view _PatchMSetIso
381 instance (Ord a, FromJSON a) => FromJSON (PatchMSet a) where
382 parseJSON = fmap (_PatchMSetIso #) . parseJSON
384 instance (Ord a, Arbitrary a) => Arbitrary (PatchMSet a) where
385 arbitrary = (PatchMSet . PM.fromMap) <$> arbitrary
387 instance ToSchema a => ToSchema (PatchMSet a) where
389 declareNamedSchema _ = wellNamedSchema "" (Proxy :: Proxy TODO)
391 type instance Patched (PatchMSet a) = MSet a
393 instance (Eq a, Arbitrary a) => Arbitrary (Replace a) where
394 arbitrary = uncurry replace <$> arbitrary
395 -- If they happen to be equal then the patch is Keep.
397 instance ToSchema a => ToSchema (Replace a) where
398 declareNamedSchema (_ :: Proxy (Replace a)) = do
399 -- TODO Keep constructor is not supported here.
400 aSchema <- declareSchemaRef (Proxy :: Proxy a)
401 return $ NamedSchema (Just "Replace") $ mempty
402 & type_ ?~ SwaggerObject
404 InsOrdHashMap.fromList
408 & required .~ [ "old", "new" ]
411 = NgramsPatch { _patch_children :: !(PatchMSet NgramsTerm)
412 , _patch_list :: !(Replace ListType) -- TODO Map UserId ListType
414 | NgramsReplace { _patch_old :: !(Maybe NgramsRepoElement)
415 , _patch_new :: !(Maybe NgramsRepoElement)
417 deriving (Eq, Show, Generic)
419 -- The JSON encoding is untagged, this is OK since the field names are disjoints and thus the encoding is unambiguous.
420 -- TODO: the empty object should be accepted and treated as mempty.
421 deriveJSON (unPrefixUntagged "_") ''NgramsPatch
422 makeLenses ''NgramsPatch
424 -- TODO: This instance is simplified since we should either have the fields children and/or list
425 -- or the fields old and/or new.
426 instance ToSchema NgramsPatch where
427 declareNamedSchema _ = do
428 childrenSch <- declareSchemaRef (Proxy :: Proxy (PatchMSet NgramsTerm))
429 listSch <- declareSchemaRef (Proxy :: Proxy (Replace ListType))
430 nreSch <- declareSchemaRef (Proxy :: Proxy NgramsRepoElement)
431 return $ NamedSchema (Just "NgramsPatch") $ mempty
432 & type_ ?~ SwaggerObject
434 InsOrdHashMap.fromList
435 [ ("children", childrenSch)
441 instance Arbitrary NgramsPatch where
442 arbitrary = frequency [ (9, NgramsPatch <$> arbitrary <*> (replace <$> arbitrary <*> arbitrary))
443 , (1, NgramsReplace <$> arbitrary <*> arbitrary)
446 instance Serialise NgramsPatch
447 instance Serialise (Replace ListType)
449 instance Serialise ListType
451 type NgramsPatchIso =
452 MaybePatch NgramsRepoElement (PairPatch (PatchMSet NgramsTerm) (Replace ListType))
454 _NgramsPatch :: Iso' NgramsPatch NgramsPatchIso
455 _NgramsPatch = iso unwrap wrap
457 unwrap (NgramsPatch c l) = Mod $ PairPatch (c, l)
458 unwrap (NgramsReplace o n) = replace o n
461 Just (PairPatch (c, l)) -> NgramsPatch c l
462 Nothing -> NgramsReplace (x ^? old . _Just) (x ^? new . _Just)
464 instance Semigroup NgramsPatch where
465 p <> q = _NgramsPatch # (p ^. _NgramsPatch <> q ^. _NgramsPatch)
467 instance Monoid NgramsPatch where
468 mempty = _NgramsPatch # mempty
470 instance Validity NgramsPatch where
471 validate p = p ^. _NgramsPatch . to validate
473 instance Transformable NgramsPatch where
474 transformable p q = transformable (p ^. _NgramsPatch) (q ^. _NgramsPatch)
476 conflicts p q = conflicts (p ^. _NgramsPatch) (q ^. _NgramsPatch)
478 transformWith conflict p q = (_NgramsPatch # p', _NgramsPatch # q')
480 (p', q') = transformWith conflict (p ^. _NgramsPatch) (q ^. _NgramsPatch)
482 type ConflictResolutionNgramsPatch =
483 ( ConflictResolutionReplace (Maybe NgramsRepoElement)
484 , ( ConflictResolutionPatchMSet NgramsTerm
485 , ConflictResolutionReplace ListType
489 type instance ConflictResolution NgramsPatch =
490 ConflictResolutionNgramsPatch
492 type PatchedNgramsPatch = Maybe NgramsRepoElement
493 type instance Patched NgramsPatch = PatchedNgramsPatch
495 instance Applicable (PairPatch (PatchMSet NgramsTerm) (Replace ListType)) NgramsRepoElement where
496 applicable (PairPatch (c, l)) n = applicable c (n ^. nre_children) <> applicable l (n ^. nre_list)
498 instance Action (PairPatch (PatchMSet NgramsTerm) (Replace ListType)) NgramsRepoElement where
499 act (PairPatch (c, l)) = (nre_children %~ act c)
500 . (nre_list %~ act l)
502 instance Applicable NgramsPatch (Maybe NgramsRepoElement) where
503 applicable p = applicable (p ^. _NgramsPatch)
505 instance Action NgramsPatch (Maybe NgramsRepoElement) where
506 act p = act (p ^. _NgramsPatch)
508 newtype NgramsTablePatch = NgramsTablePatch (PatchMap NgramsTerm NgramsPatch)
509 deriving (Eq, Show, Generic, ToJSON, FromJSON, Semigroup, Monoid, Validity, Transformable)
511 instance Serialise NgramsTablePatch
512 instance Serialise (PatchMap NgramsTerm NgramsPatch)
514 instance FromField NgramsTablePatch
516 fromField = fromField'
518 instance FromField (PatchMap TableNgrams.NgramsType (PatchMap NodeId NgramsTablePatch))
520 fromField = fromField'
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)
537 ngramsElementToRepo :: NgramsElement -> NgramsRepoElement
539 (NgramsElement { _ne_size = s
553 ngramsElementFromRepo :: NgramsTerm -> NgramsRepoElement -> NgramsElement
554 ngramsElementFromRepo
563 NgramsElement { _ne_size = s
568 , _ne_ngrams = ngrams
569 , _ne_occurrences = panic $ "API.Ngrams._ne_occurrences"
571 -- Here we could use 0 if we want to avoid any `panic`.
572 -- It will not happen using getTableNgrams if
573 -- getOccByNgramsOnly provides a count of occurrences for
574 -- all the ngrams given.
578 reRootChildren :: NgramsTerm -> ReParent NgramsTerm
579 reRootChildren root ngram = do
580 nre <- use $ at ngram
581 forOf_ (_Just . nre_children . folded) nre $ \child -> do
582 at child . _Just . nre_root ?= root
583 reRootChildren root child
585 reParent :: Maybe RootParent -> ReParent NgramsTerm
586 reParent rp child = do
587 at child . _Just %= ( (nre_parent .~ (_rp_parent <$> rp))
588 . (nre_root .~ (_rp_root <$> rp))
590 reRootChildren (fromMaybe child (rp ^? _Just . rp_root)) child
592 reParentAddRem :: RootParent -> NgramsTerm -> ReParent AddRem
593 reParentAddRem rp child p =
594 reParent (if isRem p then Nothing else Just rp) child
596 reParentNgramsPatch :: NgramsTerm -> ReParent NgramsPatch
597 reParentNgramsPatch parent ngramsPatch = do
598 root_of_parent <- use (at parent . _Just . nre_root)
600 root = fromMaybe parent root_of_parent
601 rp = RootParent { _rp_root = root, _rp_parent = parent }
602 itraverse_ (reParentAddRem rp) (ngramsPatch ^. patch_children . _PatchMSet . _PatchMap)
603 -- TODO FoldableWithIndex/TraversableWithIndex for PatchMap
605 reParentNgramsTablePatch :: ReParent NgramsTablePatch
606 reParentNgramsTablePatch p = itraverse_ reParentNgramsPatch (p ^. _NgramsTablePatch. _PatchMap)
607 -- TODO FoldableWithIndex/TraversableWithIndex for PatchMap
609 ------------------------------------------------------------------------
611 instance Action NgramsTablePatch (Maybe NgramsTableMap) where
613 fmap (execState (reParentNgramsTablePatch p)) .
614 act (p ^. _NgramsTablePatch)
616 instance Arbitrary NgramsTablePatch where
617 arbitrary = NgramsTablePatch <$> PM.fromMap <$> arbitrary
619 -- Should it be less than an Lens' to preserve PatchMap's abstraction.
620 -- ntp_ngrams_patches :: Lens' NgramsTablePatch (Map NgramsTerm NgramsPatch)
621 -- ntp_ngrams_patches = _NgramsTablePatch . undefined
623 type ReParent a = forall m. MonadState NgramsTableMap m => a -> m ()
625 ------------------------------------------------------------------------
628 data Versioned a = Versioned
629 { _v_version :: Version
632 deriving (Generic, Show, Eq)
633 deriveJSON (unPrefix "_v_") ''Versioned
634 makeLenses ''Versioned
635 instance (Typeable a, ToSchema a) => ToSchema (Versioned a) where
636 declareNamedSchema = wellNamedSchema "_v_"
637 instance Arbitrary a => Arbitrary (Versioned a) where
638 arbitrary = Versioned 1 <$> arbitrary -- TODO 1 is constant so far
640 ------------------------------------------------------------------------
642 { _r_version :: !Version
645 -- first patch in the list is the most recent
649 instance (FromJSON s, FromJSON p) => FromJSON (Repo s p) where
650 parseJSON = genericParseJSON $ unPrefix "_r_"
652 instance (ToJSON s, ToJSON p) => ToJSON (Repo s p) where
653 toJSON = genericToJSON $ unPrefix "_r_"
654 toEncoding = genericToEncoding $ unPrefix "_r_"
656 instance (Serialise s, Serialise p) => Serialise (Repo s p)
660 initRepo :: Monoid s => Repo s p
661 initRepo = Repo 1 mempty []
663 type NgramsRepo = Repo NgramsState NgramsStatePatch
664 type NgramsState = Map TableNgrams.NgramsType (Map NodeId NgramsTableMap)
665 type NgramsStatePatch = PatchMap TableNgrams.NgramsType (PatchMap NodeId NgramsTablePatch)
667 instance Serialise (PM.PatchMap NodeId NgramsTablePatch)
668 instance Serialise NgramsStatePatch
670 initMockRepo :: NgramsRepo
671 initMockRepo = Repo 1 s []
673 s = Map.singleton TableNgrams.NgramsTerms
674 $ Map.singleton 47254
676 [ (n ^. ne_ngrams, ngramsElementToRepo n) | n <- mockTable ^. _NgramsTable ]
678 data RepoEnv = RepoEnv
679 { _renv_var :: !(MVar NgramsRepo)
680 , _renv_saver :: !(IO ())
681 , _renv_lock :: !FileLock
687 class HasRepoVar env where
688 repoVar :: Getter env (MVar NgramsRepo)
690 instance HasRepoVar (MVar NgramsRepo) where
693 class HasRepoSaver env where
694 repoSaver :: Getter env (IO ())
696 class (HasRepoVar env, HasRepoSaver env) => HasRepo env where
697 repoEnv :: Getter env RepoEnv
699 instance HasRepo RepoEnv where
702 instance HasRepoVar RepoEnv where
705 instance HasRepoSaver RepoEnv where
706 repoSaver = renv_saver
708 type RepoCmdM env err m =
714 type QueryParamR = QueryParam' '[Required, Strict]
718 instance Arbitrary NgramsRepoElement where
719 arbitrary = elements $ map ngramsElementToRepo ns
721 NgramsTable ns = mockTable
724 instance FromHttpApiData (Map TableNgrams.NgramsType (Versioned NgramsTableMap))
726 parseUrlPiece x = maybeToEither x (decode $ cs x)
729 ngramsTypeFromTabType :: TabType -> TableNgrams.NgramsType
730 ngramsTypeFromTabType tabType =
731 let lieu = "Garg.API.Ngrams: " :: Text in
733 Sources -> TableNgrams.Sources
734 Authors -> TableNgrams.Authors
735 Institutes -> TableNgrams.Institutes
736 Terms -> TableNgrams.NgramsTerms
737 _ -> panic $ lieu <> "No Ngrams for this tab"
738 -- TODO: This `panic` would disapear with custom NgramsType.
743 data UpdateTableNgramsCharts = UpdateTableNgramsCharts
744 { _utn_tab_type :: !TabType
745 , _utn_list_id :: !ListId
746 } deriving (Eq, Show, Generic)
748 makeLenses ''UpdateTableNgramsCharts
749 instance FromJSON UpdateTableNgramsCharts where
750 parseJSON = genericParseJSON $ jsonOptions "_utn_"
751 instance ToSchema UpdateTableNgramsCharts where
752 declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "_utn_")