Unverified Commit f1f4726a authored by Nicolas Pouillard's avatar Nicolas Pouillard

Merge branch 'dev-ngrams-repo' of...

Merge branch 'dev-ngrams-repo' of https://gitlab.iscpif.fr/gargantext/haskell-gargantext into dev-ngrams-repo
parents 7ebc45f6 80c9a609
Pipeline #177 failed with stage
...@@ -34,6 +34,7 @@ add get ...@@ -34,6 +34,7 @@ add get
module Gargantext.API.Ngrams module Gargantext.API.Ngrams
where where
--import Debug.Trace (trace)
import Prelude (Enum, Bounded, Semigroup(..), minBound, maxBound {-, round-}, error) import Prelude (Enum, Bounded, Semigroup(..), minBound, maxBound {-, round-}, error)
-- import Gargantext.Database.Schema.User (UserId) -- import Gargantext.Database.Schema.User (UserId)
import Data.Functor (($>)) import Data.Functor (($>))
...@@ -45,6 +46,7 @@ import qualified Data.Map.Strict.Patch as PM ...@@ -45,6 +46,7 @@ import qualified Data.Map.Strict.Patch as PM
import Data.Monoid import Data.Monoid
--import Data.Semigroup --import Data.Semigroup
import Data.Set (Set) import Data.Set (Set)
-- import qualified Data.List as List
-- import Data.Maybe (isJust) -- import Data.Maybe (isJust)
-- import Data.Tuple.Extra (first) -- import Data.Tuple.Extra (first)
import qualified Data.Map.Strict as Map import qualified Data.Map.Strict as Map
...@@ -562,15 +564,15 @@ makeLenses ''Repo ...@@ -562,15 +564,15 @@ makeLenses ''Repo
initRepo :: Monoid s => Repo s p initRepo :: Monoid s => Repo s p
initRepo = Repo 1 mempty [] initRepo = Repo 1 mempty []
type NgramsRepo = Repo NgramsState NgramsStatePatch
type NgramsState = Map NgramsType (Map NodeId NgramsTableMap) type NgramsState = Map NgramsType (Map NodeId NgramsTableMap)
type NgramsStatePatch = PatchMap NgramsType (PatchMap NodeId NgramsTablePatch) type NgramsStatePatch = PatchMap NgramsType (PatchMap NodeId NgramsTablePatch)
type NgramsRepo = Repo NgramsState NgramsStatePatch
initMockRepo :: NgramsRepo initMockRepo :: NgramsRepo
initMockRepo = Repo 1 s [] initMockRepo = Repo 1 s []
where where
s = Map.singleton Ngrams.NgramsTerms s = Map.singleton Ngrams.NgramsTerms
$ Map.singleton 1 $ Map.singleton 47254
$ Map.fromList $ Map.fromList
[ (n ^. ne_ngrams, n) | n <- mockTable ^. _NgramsTable ] [ (n ^. ne_ngrams, n) | n <- mockTable ^. _NgramsTable ]
...@@ -632,7 +634,7 @@ insertNewListOfNgramsElements listId ngramsType nes = do ...@@ -632,7 +634,7 @@ insertNewListOfNgramsElements listId ngramsType nes = do
m = Map.fromList $ (\n -> (n ^. ne_ngrams, n)) <$> nes m = Map.fromList $ (\n -> (n ^. ne_ngrams, n)) <$> nes
-- Apply the given patch to the DB and returns the patch to be applied on the -- Apply the given patch to the DB and returns the patch to be applied on the
-- cilent. -- client.
-- TODO: -- TODO:
-- In this perliminary version the OT aspect is missing, therefore the version -- In this perliminary version the OT aspect is missing, therefore the version
-- number is always 1 and the returned patch is always empty. -- number is always 1 and the returned patch is always empty.
...@@ -729,10 +731,15 @@ getTableNgrams _cId maybeTabType listIds mlimit moffset = do ...@@ -729,10 +731,15 @@ getTableNgrams _cId maybeTabType listIds mlimit moffset = do
. at ngramsType . _Just . at ngramsType . _Just
. taking limit_ (dropping offset_ each) . 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 <- ngramsTableDatas <-
Ngrams.getNgramsTableDb NodeDocument ngramsType (Ngrams.NgramsTableParam listId cId) limit_ offset_ Ngrams.getNgramsTableDb NodeDocument ngramsType (Ngrams.NgramsTableParam listId cId) limit_ offset_
......
...@@ -299,7 +299,7 @@ flowList uId cId _ngs = do ...@@ -299,7 +299,7 @@ flowList uId cId _ngs = do
pure lId pure lId
flowListUser :: FlowCmdM env err m flowListUser :: FlowCmdM env err m
=> UserId -> CorpusId -> Int -> m NodeId => UserId -> CorpusId -> Int -> m ListId
flowListUser uId cId n = do flowListUser uId cId n = do
lId <- getOrMkList cId uId lId <- getOrMkList cId uId
-- is <- insertLists lId $ ngrams2list ngs -- 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