Commit 80c9a609 authored by Alexandre Delanoë's avatar Alexandre Delanoë

[READING] proposal: keeping data consistency with database.

parent 4fafc5c0
......@@ -34,6 +34,7 @@ add get
module Gargantext.API.Ngrams
where
--import Debug.Trace (trace)
import Prelude (Enum, Bounded, Semigroup(..), minBound, maxBound {-, round-}, error)
-- import Gargantext.Database.Schema.User (UserId)
import Data.Functor (($>))
......@@ -45,6 +46,7 @@ import qualified Data.Map.Strict.Patch as PM
import Data.Monoid
--import Data.Semigroup
import Data.Set (Set)
import qualified Data.List as List
-- import Data.Maybe (isJust)
-- import Data.Tuple.Extra (first)
import qualified Data.Map.Strict as Map
......@@ -564,14 +566,14 @@ makeLenses ''Repo
initRepo :: Monoid s => Repo s p
initRepo = Repo 1 mempty []
type NgramsRepo = Repo NgramsState NgramsStatePatch
type NgramsState = Map ListId (Map NgramsType NgramsTableMap)
type NgramsStatePatch = PatchMap ListId (PatchMap NgramsType NgramsTablePatch)
type NgramsRepo = Repo NgramsState NgramsStatePatch
initMockRepo :: NgramsRepo
initMockRepo = Repo 1 s []
where
s = Map.singleton 1
s = Map.singleton 47254
$ Map.singleton Ngrams.NgramsTerms
$ Map.fromList
[ (n ^. ne_ngrams, n) | n <- mockTable ^. _NgramsTable ]
......@@ -628,7 +630,7 @@ insertNewListOfNgramsElements listId m = do
m' = (Map.fromList . fmap (\n -> (n ^. ne_ngrams, n))) <$> m
-- Apply the given patch to the DB and returns the patch to be applied on the
-- cilent.
-- client.
-- TODO:
-- In this perliminary version the OT aspect is missing, therefore the version
-- number is always 1 and the returned patch is always empty.
......@@ -698,9 +700,14 @@ getTableNgrams cId maybeTabType maybeListId mlimit moffset = do
. at ngramsType . _Just
. taking limit_ (dropping offset_ each)
pure $ Versioned (repo ^. r_version) (NgramsTable ngrams)
let ngrams' = case List.null ngrams of
True -> [] -- buildRepoFromDb (TODO sync with DB at shutdown)
False -> ngrams
{-
pure $ Versioned (repo ^. r_version) (NgramsTable ngrams')
{-
buildRepoFromDb listId = do
ngramsTableDatas <-
Ngrams.getNgramsTableDb NodeDocument ngramsType (Ngrams.NgramsTableParam listId cId) limit_ offset_
......
......@@ -293,7 +293,7 @@ flowList uId cId _ngs = do
pure lId
flowListUser :: RepoCmdM env err m
=> UserId -> CorpusId -> Int -> m NodeId
=> UserId -> CorpusId -> Int -> m ListId
flowListUser uId cId n = do
lId <- getOrMkList cId uId
-- is <- insertLists lId $ ngrams2list ngs
......
Markdown is supported
0% or
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment