Commit 92d85f76 authored by Alexandre Delanoë's avatar Alexandre Delanoë

[BIN] upgrade binary for PosTags

parent e7491362
Pipeline #1364 failed with stage
......@@ -15,31 +15,33 @@ Import a corpus binary.
module Main where
import Gargantext.API.Admin.EnvTypes (DevEnv)
import Gargantext.API.Dev (withDevEnv, runCmdDev)
import Gargantext.API.Prelude (GargError)
import Gargantext.API.Node () -- instances only
import Gargantext.Database.Admin.Types.Node
import Gargantext.Database.Admin.Types.Hyperdata
import Gargantext.Database.Query.Table.Node.UpdateOpaleye
import Gargantext.Database.Prelude (Cmd, )
import Gargantext.Database.Prelude (Cmd'', )
import Gargantext.Prelude
import System.Environment (getArgs)
-- | PosTag
import Gargantext.Database.Action.Flow (indexAllDocumentsWithPosTag)
import Gargantext.Database.Query.Table.NgramsPostag (createTable_NgramsPostag)
main :: IO ()
main = do
[iniPath] <- getArgs
let
updateNodes :: Cmd GargError [Int64]
updateNodes = updateNodesWithType_
NodeList
defaultHyperdataList
upgrade :: Cmd'' DevEnv GargError ()
upgrade = do
_ <- createTable_NgramsPostag
_ <- indexAllDocumentsWithPosTag
pure ()
withDevEnv iniPath $ \env -> do
x <- runCmdDev env updateNodes
putStrLn $ show x
_ <- runCmdDev env upgrade
putStrLn "Uprade"
pure ()
......@@ -58,6 +58,7 @@ library:
- Gargantext.Database.Query.Table.User
- Gargantext.Database.Query.Table.Node
- Gargantext.Database.Query.Table.Node.UpdateOpaleye
- Gargantext.Database.Query.Table.NgramsPostag
- Gargantext.Database.Prelude
- Gargantext.Database.Admin.Trigger.Init
- Gargantext.Database.Admin.Config
......
......@@ -91,7 +91,7 @@ groupWith (GroupWithPosTag _ _ m) t =
Nothing -> clean t
Just t' -> clean $ NgramsTerm t'
where
clean (NgramsTerm t) = NgramsTerm $ Text.replace "-" " " t
clean (NgramsTerm t'') = NgramsTerm $ Text.replace "-" " " t''
--------------------------------------------------------------------
stemPatches :: GroupParams
......
......@@ -41,7 +41,7 @@ module Gargantext.Database.Action.Flow -- (flowDatabase, ngrams2list)
, allDataOrigins
, do_api
, upgrade
, indexAllDocumentsWithPosTag
)
where
......@@ -439,14 +439,14 @@ instance HasText a => HasText (Node a)
-- | TODO putelsewhere
-- | Upgrade function
-- Suppose all documents are English (this is the case actually)
upgrade :: FlowCmdM env err m => m ()
upgrade = do
indexAllDocumentsWithPosTag :: FlowCmdM env err m => m ()
indexAllDocumentsWithPosTag = do
rootId <- getRootId (UserName userMaster)
corpusIds <- findNodesId rootId [NodeCorpus]
docs <- List.concat <$> mapM getDocumentsWithParentId [NodeId 5]
docs <- List.concat <$> mapM getDocumentsWithParentId corpusIds
printDebug "Nb of docs" (List.length docs)
......@@ -458,7 +458,7 @@ upgrade = do
(extractNgramsT $ withLang (Multi EN) documentsWithId)
documentsWithId
terms2id <- insertExtractedNgrams $ HashMap.keys mapNgramsDocs'
_ <- insertExtractedNgrams $ HashMap.keys mapNgramsDocs'
pure ()
......
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