Commit 2b4c4297 authored by Grégoire Locqueville's avatar Grégoire Locqueville

Finished, but issues remain

If reusing parent list: subterms get dropped.
If building a new list: two term lists are created, but both are empty.
parent df88acde
......@@ -177,6 +177,7 @@ library
Gargantext.Core.NodeStory.Types
Gargantext.Core.Text
Gargantext.Core.Text.Context
Gargantext.Core.Text.Corpus
Gargantext.Core.Text.Corpus.API
Gargantext.Core.Text.Corpus.API.Arxiv
Gargantext.Core.Text.Corpus.API.EPO
......
module Gargantext.Database.Action.Corpus where
module Gargantext.Core.Text.Corpus (makeSubcorpusFromQuery) where
import Data.Set.Internal qualified as Set
import Gargantext.API.Admin.Types (HasSettings)
......@@ -51,8 +51,9 @@ makeSubcorpusFromQuery user parentId query reuseParentList = do
-- Create nodes for docs and terms as children of the subcorpus
void $ insertDefaultNode NodeTexts subcorpusId userId
listId <- insertDefaultNode NodeList subcorpusId userId
-- Either simply copy parent terms... (TODO)
if reuseParentList then void $ copyNode True _parentList subcorpusId
-- Either simply copy parent terms...
-- (TODO this does not keep subterms)
if reuseParentList then void $ copyNode True listId subcorpusId
-- ... or rebuild a term list from scratch
else do
ngrams <- buildNgramsLists
......@@ -71,11 +72,3 @@ makeSubcorpusFromQuery user parentId query reuseParentList = do
-- _ <- updateContextScore userCorpusId listId
-- _ <- updateNgramsOccurrences userCorpusId listId
return subcorpusId
-- TODO
-- Permettre de (mettre les 2 en option) :
-- [X] 1a. relancer le buildNgramsLists (cf. module Flow)
-- [ ] 1b. ou copier la liste (WIP)
-- [ ] Vérifier l'étape de réindexation reIndexWith
-- [ ] 2. générer un graphe
module REPL where
import Gargantext.API.Admin.Types (HasSettings)
import Gargantext.API.Dev (runCmdReplEasy)
import Gargantext.API.Errors.Types (BackendInternalError)
import Gargantext.Core.NLP (HasNLPServer)
import Gargantext.Core.NodeStory.Types (HasNodeStory)
import Gargantext.Core.Text.Corpus.Query qualified as Q
import Gargantext.Core.Types.Individu (User (..))
import Gargantext.Database.Action.Corpus (makeSubcorpusFromQuery)
import Gargantext.Database.Admin.Types.Node (CorpusId)
import Gargantext.Database.Prelude (DbCmd')
import Gargantext.Database.Query.Tree.Error (HasTreeError)
import Gargantext.Prelude
execText :: IO (Maybe CorpusId)
execText = runCmdReplEasy $ testSubcorpusFunction "user1" 133 "information" False
testSubcorpusFunction ::
forall env m. ( DbCmd' env BackendInternalError m
, HasNodeStory env BackendInternalError m
, HasNLPServer env
, HasNLPServer env
, HasTreeError BackendInternalError
, HasSettings env
)
=> Text -- ^ Username
-> CorpusId -- ^ Parent corpus ID
-> Text -- ^ The query, in text form
-> Bool -- ^ Whether to reuse parent term list (True) or compute a new one
-- based only on the documents in the subcorpus (False)
-> m (Maybe CorpusId)
testSubcorpusFunction username parentId queryText reuseParentList =
let eitherQuery = Q.parseQuery . Q.RawQuery $ queryText in
case eitherQuery of
Left _ -> return Nothing -- putStrLn ("Error parsing query " <> queryText) >> return Nothing -- TODO emit an actual error
Right query -> Just <$> makeSubcorpusFromQuery (UserName username) parentId query reuseParentList
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