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 Data.Hashable (Hashable)
23 import qualified Data.HashMap.Strict.InsOrd as InsOrdHashMap
24 import qualified Data.List as List
25 import Data.Map.Strict (Map)
26 import qualified Data.Map.Strict as Map
27 import qualified Data.Map.Strict.Patch as PM
28 import Data.Maybe (fromMaybe)
30 import Data.Patch.Class (Replace, replace, Action(act), Group, Applicable(..), Composable(..), Transformable(..),
31 PairPatch(..), Patched, ConflictResolution, ConflictResolutionReplace,
32 MaybePatch(Mod), unMod, old, new)
34 import qualified Data.Set as Set
35 import Data.String (IsString, fromString)
36 import Data.Swagger hiding (version, patch)
37 import Data.Text (Text, pack, strip)
39 import Database.PostgreSQL.Simple.FromField (FromField, fromField, ResultError(ConversionFailed), returnError)
40 import GHC.Generics (Generic)
41 import Servant hiding (Patch)
42 import Servant.Job.Utils (jsonOptions)
43 import System.FileLock (FileLock)
44 import Test.QuickCheck (elements, frequency)
45 import Test.QuickCheck.Arbitrary (Arbitrary, arbitrary)
47 import Protolude (maybeToEither)
48 import Gargantext.Prelude
50 import Gargantext.Prelude.Crypto.Hash (IsHashable(..))
51 import Gargantext.Core.Text (size)
52 import Gargantext.Core.Types (ListType(..), ListId, NodeId)
53 import Gargantext.Core.Types (TODO)
54 import Gargantext.Core.Utils.Prefix (unPrefix, unPrefixUntagged, unPrefixSwagger, wellNamedSchema)
55 import Gargantext.Database.Prelude (fromField', CmdM', HasConnectionPool, HasConfig)
56 import qualified Gargantext.Database.Query.Table.Ngrams as TableNgrams
58 ------------------------------------------------------------------------
59 --data FacetFormat = Table | Chart
60 data TabType = Docs | Trash | MoreFav | MoreTrash
61 | Terms | Sources | Authors | Institutes
63 deriving (Bounded, Enum, Eq, Generic, Ord, Show)
66 instance Hashable TabType
68 instance FromHttpApiData TabType
70 parseUrlPiece "Docs" = pure Docs
71 parseUrlPiece "Trash" = pure Trash
72 parseUrlPiece "MoreFav" = pure MoreFav
73 parseUrlPiece "MoreTrash" = pure MoreTrash
75 parseUrlPiece "Terms" = pure Terms
76 parseUrlPiece "Sources" = pure Sources
77 parseUrlPiece "Institutes" = pure Institutes
78 parseUrlPiece "Authors" = pure Authors
80 parseUrlPiece "Contacts" = pure Contacts
82 parseUrlPiece _ = Left "Unexpected value of TabType"
83 instance ToParamSchema TabType
84 instance ToJSON TabType
85 instance FromJSON TabType
86 instance ToSchema TabType
87 instance Arbitrary TabType
89 arbitrary = elements [minBound .. maxBound]
90 instance FromJSONKey TabType where
91 fromJSONKey = genericFromJSONKey defaultJSONKeyOptions
92 instance ToJSONKey TabType where
93 toJSONKey = genericToJSONKey defaultJSONKeyOptions
95 newtype MSet a = MSet (Map a ())
96 deriving (Eq, Ord, Show, Generic, Arbitrary, Semigroup, Monoid)
98 instance ToJSON a => ToJSON (MSet a) where
99 toJSON (MSet m) = toJSON (Map.keys m)
100 toEncoding (MSet m) = toEncoding (Map.keys m)
102 mSetFromSet :: Set a -> MSet a
103 mSetFromSet = MSet . Map.fromSet (const ())
105 mSetFromList :: Ord a => [a] -> MSet a
106 mSetFromList = MSet . Map.fromList . map (\x -> (x, ()))
108 -- mSetToSet :: Ord a => MSet a -> Set a
109 -- mSetToSet (MSet a) = Set.fromList ( Map.keys a)
110 mSetToSet :: Ord a => MSet a -> Set a
111 mSetToSet = Set.fromList . mSetToList
113 mSetToList :: MSet a -> [a]
114 mSetToList (MSet a) = Map.keys a
116 instance Foldable MSet where
117 foldMap f (MSet m) = Map.foldMapWithKey (\k _ -> f k) m
119 instance (Ord a, FromJSON a) => FromJSON (MSet a) where
120 parseJSON = fmap mSetFromList . parseJSON
122 instance (ToJSONKey a, ToSchema a) => ToSchema (MSet a) where
124 declareNamedSchema _ = wellNamedSchema "" (Proxy :: Proxy TODO)
126 ------------------------------------------------------------------------
127 newtype NgramsTerm = NgramsTerm { unNgramsTerm :: Text }
128 deriving (Ord, Eq, Show, Generic, ToJSONKey, ToJSON, FromJSON, Semigroup, Arbitrary, Serialise, ToSchema, Hashable)
131 instance IsHashable NgramsTerm where
132 hash (NgramsTerm t) = hash t
134 instance Monoid NgramsTerm where
135 mempty = NgramsTerm ""
137 instance FromJSONKey NgramsTerm where
138 fromJSONKey = FromJSONKeyTextParser $ \t -> pure $ NgramsTerm $ strip t
140 instance IsString NgramsTerm where
141 fromString s = NgramsTerm $ pack s
143 instance FromField NgramsTerm
145 fromField field mb = do
146 v <- fromField field mb
148 Success a -> pure $ NgramsTerm $ strip a
149 Error _err -> returnError ConversionFailed field
150 $ List.intercalate " " [ "cannot parse hyperdata for JSON: "
154 data RootParent = RootParent
155 { _rp_root :: NgramsTerm
156 , _rp_parent :: NgramsTerm
158 deriving (Ord, Eq, Show, Generic)
160 deriveJSON (unPrefix "_rp_") ''RootParent
161 makeLenses ''RootParent
163 data NgramsRepoElement = NgramsRepoElement
165 , _nre_list :: !ListType
166 , _nre_root :: !(Maybe NgramsTerm)
167 , _nre_parent :: !(Maybe NgramsTerm)
168 , _nre_children :: !(MSet NgramsTerm)
170 deriving (Ord, Eq, Show, Generic)
172 deriveJSON (unPrefix "_nre_") ''NgramsRepoElement
174 -- if ngrams & not size => size
177 makeLenses ''NgramsRepoElement
179 instance ToSchema NgramsRepoElement where
180 declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "_nre_")
182 instance Serialise (MSet NgramsTerm)
183 instance Serialise NgramsRepoElement
186 NgramsElement { _ne_ngrams :: NgramsTerm
188 , _ne_list :: ListType
189 , _ne_occurrences :: Int
190 , _ne_root :: Maybe NgramsTerm
191 , _ne_parent :: Maybe NgramsTerm
192 , _ne_children :: MSet NgramsTerm
194 deriving (Ord, Eq, Show, Generic)
196 deriveJSON (unPrefix "_ne_") ''NgramsElement
197 makeLenses ''NgramsElement
199 mkNgramsElement :: NgramsTerm
204 mkNgramsElement ngrams list rp children =
205 NgramsElement ngrams (size (unNgramsTerm ngrams)) list 1 (_rp_root <$> rp) (_rp_parent <$> rp) children
207 newNgramsElement :: Maybe ListType -> NgramsTerm -> NgramsElement
208 newNgramsElement mayList ngrams =
209 mkNgramsElement ngrams (fromMaybe MapTerm mayList) Nothing mempty
211 instance ToSchema NgramsElement where
212 declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "_ne_")
213 instance Arbitrary NgramsElement where
214 arbitrary = elements [newNgramsElement Nothing "sport"]
217 ------------------------------------------------------------------------
218 newtype NgramsTable = NgramsTable [NgramsElement]
219 deriving (Ord, Eq, Generic, ToJSON, FromJSON, Show)
221 type NgramsList = NgramsTable
223 makePrisms ''NgramsTable
225 -- | Question: why these repetition of Type in this instance
226 -- may you document it please ?
227 instance Each NgramsTable NgramsTable NgramsElement NgramsElement where
228 each = _NgramsTable . each
231 -- | TODO Check N and Weight
233 toNgramsElement :: [NgramsTableData] -> [NgramsElement]
234 toNgramsElement ns = map toNgramsElement' ns
236 toNgramsElement' (NgramsTableData _ p t _ lt w) = NgramsElement t lt' (round w) p' c'
240 Just x -> lookup x mapParent
241 c' = maybe mempty identity $ lookup t mapChildren
242 lt' = maybe (panic "API.Ngrams: listypeId") identity lt
244 mapParent :: Map Int Text
245 mapParent = Map.fromListWith (<>) $ map (\(NgramsTableData i _ t _ _ _) -> (i,t)) ns
247 mapChildren :: Map Text (Set Text)
248 mapChildren = Map.mapKeys (\i -> (maybe (panic "API.Ngrams.mapChildren: ParentId with no Terms: Impossible") identity $ lookup i mapParent))
249 $ Map.fromListWith (<>)
250 $ map (first fromJust)
251 $ filter (isJust . fst)
252 $ map (\(NgramsTableData _ p t _ _ _) -> (p, Set.singleton t)) ns
255 mockTable :: NgramsTable
256 mockTable = NgramsTable
257 [ mkNgramsElement "animal" MapTerm Nothing (mSetFromList ["dog", "cat"])
258 , mkNgramsElement "cat" MapTerm (rp "animal") mempty
259 , mkNgramsElement "cats" StopTerm Nothing mempty
260 , mkNgramsElement "dog" MapTerm (rp "animal") (mSetFromList ["dogs"])
261 , mkNgramsElement "dogs" StopTerm (rp "dog") mempty
262 , mkNgramsElement "fox" MapTerm Nothing mempty
263 , mkNgramsElement "object" CandidateTerm Nothing mempty
264 , mkNgramsElement "nothing" StopTerm Nothing mempty
265 , mkNgramsElement "organic" MapTerm Nothing (mSetFromList ["flower"])
266 , mkNgramsElement "flower" MapTerm (rp "organic") mempty
267 , mkNgramsElement "moon" CandidateTerm Nothing mempty
268 , mkNgramsElement "sky" StopTerm Nothing mempty
271 rp n = Just $ RootParent n n
273 instance Arbitrary NgramsTable where
274 arbitrary = pure mockTable
276 instance ToSchema NgramsTable
278 ------------------------------------------------------------------------
279 type NgramsTableMap = Map NgramsTerm NgramsRepoElement
280 ------------------------------------------------------------------------
281 -- On the Client side:
282 --data Action = InGroup NgramsId NgramsId
283 -- | OutGroup NgramsId NgramsId
284 -- | SetListType NgramsId ListType
286 data PatchSet a = PatchSet
290 deriving (Eq, Ord, Show, Generic)
292 makeLenses ''PatchSet
293 makePrisms ''PatchSet
295 instance ToJSON a => ToJSON (PatchSet a) where
296 toJSON = genericToJSON $ unPrefix "_"
297 toEncoding = genericToEncoding $ unPrefix "_"
299 instance (Ord a, FromJSON a) => FromJSON (PatchSet a) where
300 parseJSON = genericParseJSON $ unPrefix "_"
303 instance (Ord a, Arbitrary a) => Arbitrary (PatchSet a) where
304 arbitrary = PatchSet <$> arbitrary <*> arbitrary
306 type instance Patched (PatchSet a) = Set a
308 type ConflictResolutionPatchSet a = SimpleConflictResolution' (Set a)
309 type instance ConflictResolution (PatchSet a) = ConflictResolutionPatchSet a
311 instance Ord a => Semigroup (PatchSet a) where
312 p <> q = PatchSet { _rem = (q ^. rem) `Set.difference` (p ^. add) <> p ^. rem
313 , _add = (q ^. add) `Set.difference` (p ^. rem) <> p ^. add
316 instance Ord a => Monoid (PatchSet a) where
317 mempty = PatchSet mempty mempty
319 instance Ord a => Group (PatchSet a) where
320 invert (PatchSet r a) = PatchSet a r
322 instance Ord a => Composable (PatchSet a) where
323 composable _ _ = undefined
325 instance Ord a => Action (PatchSet a) (Set a) where
326 act p source = (source `Set.difference` (p ^. rem)) <> p ^. add
328 instance Applicable (PatchSet a) (Set a) where
329 applicable _ _ = mempty
331 instance Ord a => Validity (PatchSet a) where
332 validate p = check (Set.disjoint (p ^. rem) (p ^. add)) "_rem and _add should be dijoint"
334 instance Ord a => Transformable (PatchSet a) where
335 transformable = undefined
337 conflicts _p _q = undefined
339 transformWith conflict p q = undefined conflict p q
341 instance ToSchema a => ToSchema (PatchSet a)
344 type AddRem = Replace (Maybe ())
346 instance Serialise AddRem
348 remPatch, addPatch :: AddRem
349 remPatch = replace (Just ()) Nothing
350 addPatch = replace Nothing (Just ())
352 isRem :: Replace (Maybe ()) -> Bool
353 isRem = (== remPatch)
355 type PatchMap = PM.PatchMap
357 newtype PatchMSet a = PatchMSet (PatchMap a AddRem)
358 deriving (Eq, Show, Generic, Validity, Semigroup, Monoid, Group,
359 Transformable, Composable)
361 unPatchMSet :: PatchMSet a -> PatchMap a AddRem
362 unPatchMSet (PatchMSet a) = a
364 type ConflictResolutionPatchMSet a = a -> ConflictResolutionReplace (Maybe ())
365 type instance ConflictResolution (PatchMSet a) = ConflictResolutionPatchMSet a
367 instance (Serialise a, Ord a) => Serialise (PatchMap a AddRem)
368 instance (Serialise a, Ord a) => Serialise (PatchMSet a)
370 -- TODO this breaks module abstraction
371 makePrisms ''PM.PatchMap
373 makePrisms ''PatchMSet
375 _PatchMSetIso :: Ord a => Iso' (PatchMSet a) (PatchSet a)
376 _PatchMSetIso = _PatchMSet . _PatchMap . iso f g . from _PatchSet
378 f :: Ord a => Map a (Replace (Maybe ())) -> (Set a, Set a)
379 f = Map.partition isRem >>> both %~ Map.keysSet
381 g :: Ord a => (Set a, Set a) -> Map a (Replace (Maybe ()))
382 g (rems, adds) = Map.fromSet (const remPatch) rems
383 <> Map.fromSet (const addPatch) adds
385 instance Ord a => Action (PatchMSet a) (MSet a) where
386 act (PatchMSet p) (MSet m) = MSet $ act p m
388 instance Ord a => Applicable (PatchMSet a) (MSet a) where
389 applicable (PatchMSet p) (MSet m) = applicable p m
391 instance (Ord a, ToJSON a) => ToJSON (PatchMSet a) where
392 toJSON = toJSON . view _PatchMSetIso
393 toEncoding = toEncoding . view _PatchMSetIso
395 instance (Ord a, FromJSON a) => FromJSON (PatchMSet a) where
396 parseJSON = fmap (_PatchMSetIso #) . parseJSON
398 instance (Ord a, Arbitrary a) => Arbitrary (PatchMSet a) where
399 arbitrary = (PatchMSet . PM.fromMap) <$> arbitrary
401 instance ToSchema a => ToSchema (PatchMSet a) where
403 declareNamedSchema _ = wellNamedSchema "" (Proxy :: Proxy TODO)
405 type instance Patched (PatchMSet a) = MSet a
407 instance (Eq a, Arbitrary a) => Arbitrary (Replace a) where
408 arbitrary = uncurry replace <$> arbitrary
409 -- If they happen to be equal then the patch is Keep.
411 instance ToSchema a => ToSchema (Replace a) where
412 declareNamedSchema (_ :: Proxy (Replace a)) = do
413 -- TODO Keep constructor is not supported here.
414 aSchema <- declareSchemaRef (Proxy :: Proxy a)
415 return $ NamedSchema (Just "Replace") $ mempty
416 & type_ ?~ SwaggerObject
418 InsOrdHashMap.fromList
422 & required .~ [ "old", "new" ]
425 = NgramsPatch { _patch_children :: !(PatchMSet NgramsTerm)
426 , _patch_list :: !(Replace ListType) -- TODO Map UserId ListType
428 | NgramsReplace { _patch_old :: !(Maybe NgramsRepoElement)
429 , _patch_new :: !(Maybe NgramsRepoElement)
431 deriving (Eq, Show, Generic)
433 -- The JSON encoding is untagged, this is OK since the field names are disjoints and thus the encoding is unambiguous.
434 -- TODO: the empty object should be accepted and treated as mempty.
435 deriveJSON (unPrefixUntagged "_") ''NgramsPatch
436 makeLenses ''NgramsPatch
438 -- TODO: This instance is simplified since we should either have the fields children and/or list
439 -- or the fields old and/or new.
440 instance ToSchema NgramsPatch where
441 declareNamedSchema _ = do
442 childrenSch <- declareSchemaRef (Proxy :: Proxy (PatchMSet NgramsTerm))
443 listSch <- declareSchemaRef (Proxy :: Proxy (Replace ListType))
444 nreSch <- declareSchemaRef (Proxy :: Proxy NgramsRepoElement)
445 return $ NamedSchema (Just "NgramsPatch") $ mempty
446 & type_ ?~ SwaggerObject
448 InsOrdHashMap.fromList
449 [ ("children", childrenSch)
455 instance Arbitrary NgramsPatch where
456 arbitrary = frequency [ (9, NgramsPatch <$> arbitrary <*> (replace <$> arbitrary <*> arbitrary))
457 , (1, NgramsReplace <$> arbitrary <*> arbitrary)
460 instance Serialise NgramsPatch
461 instance Serialise (Replace ListType)
463 instance Serialise ListType
465 type NgramsPatchIso =
466 MaybePatch NgramsRepoElement (PairPatch (PatchMSet NgramsTerm) (Replace ListType))
468 _NgramsPatch :: Iso' NgramsPatch NgramsPatchIso
469 _NgramsPatch = iso unwrap wrap
471 unwrap (NgramsPatch c l) = Mod $ PairPatch (c, l)
472 unwrap (NgramsReplace o n) = replace o n
475 Just (PairPatch (c, l)) -> NgramsPatch c l
476 Nothing -> NgramsReplace (x ^? old . _Just) (x ^? new . _Just)
478 instance Semigroup NgramsPatch where
479 p <> q = _NgramsPatch # (p ^. _NgramsPatch <> q ^. _NgramsPatch)
481 instance Monoid NgramsPatch where
482 mempty = _NgramsPatch # mempty
484 instance Validity NgramsPatch where
485 validate p = p ^. _NgramsPatch . to validate
487 instance Transformable NgramsPatch where
488 transformable p q = transformable (p ^. _NgramsPatch) (q ^. _NgramsPatch)
490 conflicts p q = conflicts (p ^. _NgramsPatch) (q ^. _NgramsPatch)
492 transformWith conflict p q = (_NgramsPatch # p', _NgramsPatch # q')
494 (p', q') = transformWith conflict (p ^. _NgramsPatch) (q ^. _NgramsPatch)
496 type ConflictResolutionNgramsPatch =
497 ( ConflictResolutionReplace (Maybe NgramsRepoElement)
498 , ( ConflictResolutionPatchMSet NgramsTerm
499 , ConflictResolutionReplace ListType
503 type instance ConflictResolution NgramsPatch =
504 ConflictResolutionNgramsPatch
506 type PatchedNgramsPatch = Maybe NgramsRepoElement
507 type instance Patched NgramsPatch = PatchedNgramsPatch
509 instance Applicable (PairPatch (PatchMSet NgramsTerm) (Replace ListType)) NgramsRepoElement where
510 applicable (PairPatch (c, l)) n = applicable c (n ^. nre_children) <> applicable l (n ^. nre_list)
512 instance Action (PairPatch (PatchMSet NgramsTerm) (Replace ListType)) NgramsRepoElement where
513 act (PairPatch (c, l)) = (nre_children %~ act c)
514 . (nre_list %~ act l)
516 instance Applicable NgramsPatch (Maybe NgramsRepoElement) where
517 applicable p = applicable (p ^. _NgramsPatch)
519 instance Action NgramsPatch (Maybe NgramsRepoElement) where
520 act p = act (p ^. _NgramsPatch)
522 newtype NgramsTablePatch = NgramsTablePatch (PatchMap NgramsTerm NgramsPatch)
523 deriving (Eq, Show, Generic, ToJSON, FromJSON, Semigroup, Monoid, Validity, Transformable)
525 instance Serialise NgramsTablePatch
526 instance Serialise (PatchMap NgramsTerm NgramsPatch)
528 instance FromField NgramsTablePatch
530 fromField = fromField'
532 instance FromField (PatchMap TableNgrams.NgramsType (PatchMap NodeId NgramsTablePatch))
534 fromField = fromField'
536 type instance ConflictResolution NgramsTablePatch =
537 NgramsTerm -> ConflictResolutionNgramsPatch
539 type PatchedNgramsTablePatch = Map NgramsTerm PatchedNgramsPatch
540 -- ~ Patched (PatchMap NgramsTerm NgramsPatch)
541 type instance Patched NgramsTablePatch = PatchedNgramsTablePatch
543 makePrisms ''NgramsTablePatch
544 instance ToSchema (PatchMap NgramsTerm NgramsPatch)
545 instance ToSchema NgramsTablePatch
547 instance Applicable NgramsTablePatch (Maybe NgramsTableMap) where
548 applicable p = applicable (p ^. _NgramsTablePatch)
551 ngramsElementToRepo :: NgramsElement -> NgramsRepoElement
553 (NgramsElement { _ne_size = s
567 ngramsElementFromRepo :: NgramsTerm -> NgramsRepoElement -> NgramsElement
568 ngramsElementFromRepo
577 NgramsElement { _ne_size = s
582 , _ne_ngrams = ngrams
583 , _ne_occurrences = panic $ "API.Ngrams._ne_occurrences"
585 -- Here we could use 0 if we want to avoid any `panic`.
586 -- It will not happen using getTableNgrams if
587 -- getOccByNgramsOnly provides a count of occurrences for
588 -- all the ngrams given.
592 reRootChildren :: NgramsTerm -> ReParent NgramsTerm
593 reRootChildren root ngram = do
594 nre <- use $ at ngram
595 forOf_ (_Just . nre_children . folded) nre $ \child -> do
596 at child . _Just . nre_root ?= root
597 reRootChildren root child
599 reParent :: Maybe RootParent -> ReParent NgramsTerm
600 reParent rp child = do
601 at child . _Just %= ( (nre_parent .~ (_rp_parent <$> rp))
602 . (nre_root .~ (_rp_root <$> rp))
604 reRootChildren (fromMaybe child (rp ^? _Just . rp_root)) child
606 reParentAddRem :: RootParent -> NgramsTerm -> ReParent AddRem
607 reParentAddRem rp child p =
608 reParent (if isRem p then Nothing else Just rp) child
610 reParentNgramsPatch :: NgramsTerm -> ReParent NgramsPatch
611 reParentNgramsPatch parent ngramsPatch = do
612 root_of_parent <- use (at parent . _Just . nre_root)
614 root = fromMaybe parent root_of_parent
615 rp = RootParent { _rp_root = root, _rp_parent = parent }
616 itraverse_ (reParentAddRem rp) (ngramsPatch ^. patch_children . _PatchMSet . _PatchMap)
617 -- TODO FoldableWithIndex/TraversableWithIndex for PatchMap
619 reParentNgramsTablePatch :: ReParent NgramsTablePatch
620 reParentNgramsTablePatch p = itraverse_ reParentNgramsPatch (p ^. _NgramsTablePatch. _PatchMap)
621 -- TODO FoldableWithIndex/TraversableWithIndex for PatchMap
623 ------------------------------------------------------------------------
625 instance Action NgramsTablePatch (Maybe NgramsTableMap) where
627 fmap (execState (reParentNgramsTablePatch p)) .
628 act (p ^. _NgramsTablePatch)
630 instance Arbitrary NgramsTablePatch where
631 arbitrary = NgramsTablePatch <$> PM.fromMap <$> arbitrary
633 -- Should it be less than an Lens' to preserve PatchMap's abstraction.
634 -- ntp_ngrams_patches :: Lens' NgramsTablePatch (Map NgramsTerm NgramsPatch)
635 -- ntp_ngrams_patches = _NgramsTablePatch . undefined
637 type ReParent a = forall m. MonadState NgramsTableMap m => a -> m ()
639 ------------------------------------------------------------------------
642 data Versioned a = Versioned
643 { _v_version :: Version
646 deriving (Generic, Show, Eq)
647 deriveJSON (unPrefix "_v_") ''Versioned
648 makeLenses ''Versioned
649 instance (Typeable a, ToSchema a) => ToSchema (Versioned a) where
650 declareNamedSchema = wellNamedSchema "_v_"
651 instance Arbitrary a => Arbitrary (Versioned a) where
652 arbitrary = Versioned 1 <$> arbitrary -- TODO 1 is constant so far
653 ------------------------------------------------------------------------
656 data VersionedWithCount a = VersionedWithCount
657 { _vc_version :: Version
661 deriving (Generic, Show, Eq)
662 deriveJSON (unPrefix "_vc_") ''VersionedWithCount
663 makeLenses ''VersionedWithCount
664 instance (Typeable a, ToSchema a) => ToSchema (VersionedWithCount a) where
665 declareNamedSchema = wellNamedSchema "_vc_"
666 instance Arbitrary a => Arbitrary (VersionedWithCount a) where
667 arbitrary = VersionedWithCount 1 1 <$> arbitrary -- TODO 1 is constant so far
669 toVersionedWithCount :: Count -> Versioned a -> VersionedWithCount a
670 toVersionedWithCount count (Versioned version data_) = VersionedWithCount version count data_
671 ------------------------------------------------------------------------
673 { _r_version :: !Version
676 -- first patch in the list is the most recent
678 deriving (Generic, Show)
680 instance (FromJSON s, FromJSON p) => FromJSON (Repo s p) where
681 parseJSON = genericParseJSON $ unPrefix "_r_"
683 instance (ToJSON s, ToJSON p) => ToJSON (Repo s p) where
684 toJSON = genericToJSON $ unPrefix "_r_"
685 toEncoding = genericToEncoding $ unPrefix "_r_"
687 instance (Serialise s, Serialise p) => Serialise (Repo s p)
691 initRepo :: Monoid s => Repo s p
692 initRepo = Repo 1 mempty []
694 type NgramsRepo = Repo NgramsState NgramsStatePatch
695 type NgramsState = Map TableNgrams.NgramsType (Map NodeId NgramsTableMap)
696 type NgramsStatePatch = PatchMap TableNgrams.NgramsType (PatchMap NodeId NgramsTablePatch)
698 instance Serialise (PM.PatchMap NodeId NgramsTablePatch)
699 instance Serialise NgramsStatePatch
701 initMockRepo :: NgramsRepo
702 initMockRepo = Repo 1 s []
704 s = Map.singleton TableNgrams.NgramsTerms
705 $ Map.singleton 47254
707 [ (n ^. ne_ngrams, ngramsElementToRepo n) | n <- mockTable ^. _NgramsTable ]
709 data RepoEnv = RepoEnv
710 { _renv_var :: !(MVar NgramsRepo)
711 , _renv_saver :: !(IO ())
712 , _renv_lock :: !FileLock
718 class HasRepoVar env where
719 repoVar :: Getter env (MVar NgramsRepo)
721 instance HasRepoVar (MVar NgramsRepo) where
724 class HasRepoSaver env where
725 repoSaver :: Getter env (IO ())
727 class (HasRepoVar env, HasRepoSaver env) => HasRepo env where
728 repoEnv :: Getter env RepoEnv
730 instance HasRepo RepoEnv where
733 instance HasRepoVar RepoEnv where
736 instance HasRepoSaver RepoEnv where
737 repoSaver = renv_saver
739 type RepoCmdM env err m =
742 , HasConnectionPool env
747 type QueryParamR = QueryParam' '[Required, Strict]
751 instance Arbitrary NgramsRepoElement where
752 arbitrary = elements $ map ngramsElementToRepo ns
754 NgramsTable ns = mockTable
757 instance FromHttpApiData (Map TableNgrams.NgramsType (Versioned NgramsTableMap))
759 parseUrlPiece x = maybeToEither x (decode $ cs x)
762 ngramsTypeFromTabType :: TabType -> TableNgrams.NgramsType
763 ngramsTypeFromTabType tabType =
764 let lieu = "Garg.API.Ngrams: " :: Text in
766 Sources -> TableNgrams.Sources
767 Authors -> TableNgrams.Authors
768 Institutes -> TableNgrams.Institutes
769 Terms -> TableNgrams.NgramsTerms
770 _ -> panic $ lieu <> "No Ngrams for this tab"
771 -- TODO: This `panic` would disapear with custom NgramsType.
776 data UpdateTableNgramsCharts = UpdateTableNgramsCharts
777 { _utn_tab_type :: !TabType
778 , _utn_list_id :: !ListId
779 } deriving (Eq, Show, Generic)
781 makeLenses ''UpdateTableNgramsCharts
782 instance FromJSON UpdateTableNgramsCharts where
783 parseJSON = genericParseJSON $ jsonOptions "_utn_"
784 instance ToSchema UpdateTableNgramsCharts where
785 declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "_utn_")