Commit 740badb8 authored by Alexandre Delanoë's avatar Alexandre Delanoë

[BIN] import adding limit.

parent d2e8a845
...@@ -19,6 +19,7 @@ Import a corpus binary. ...@@ -19,6 +19,7 @@ Import a corpus binary.
module Main where module Main where
import Prelude (read)
import Control.Exception (finally) import Control.Exception (finally)
import Servant (ServantErr) import Servant (ServantErr)
import Gargantext.Prelude import Gargantext.Prelude
...@@ -38,31 +39,38 @@ import Control.Monad.IO.Class (liftIO) ...@@ -38,31 +39,38 @@ import Control.Monad.IO.Class (liftIO)
main :: IO () main :: IO ()
main = do main = do
[user, iniPath, name, corpusPath, users] <- getArgs [userCreate, user, name, iniPath, limit, corpusPath] <- getArgs
--{- --{-
let createUsers :: Cmd ServantErr Int64 let createUsers :: Cmd ServantErr Int64
createUsers = insertUsersDemo createUsers = insertUsersDemo
{- {-
let cmdCorpus :: forall m. FlowCmdM DevEnv ServantErr m => m CorpusId let csvCorpus :: forall m. FlowCmdM DevEnv ServantErr m => m CorpusId
cmdCorpus = flowCorpus (cs user) (cs name) (Mono EN) CsvHalFormat corpusPath csvCorpus = flowCorpus (cs user) (cs name) (Multi EN) CsvHalFormat corpusPath
--} --}
let cmdCorpus :: forall m. FlowCmdM DevEnv ServantErr m => m CorpusId let debatCorpus :: forall m. FlowCmdM DevEnv ServantErr m => m CorpusId
cmdCorpus = do debatCorpus = do
docs <- liftIO ( splitEvery 500 docs <- liftIO ( splitEvery 500
<$> take 10000 <$> take (read limit :: Int)
<$> readFile corpusPath <$> readFile corpusPath
:: IO [[GrandDebatReference ]] :: IO [[GrandDebatReference ]]
) )
flowCorpus (Text.pack user) (Text.pack name) (Multi FR) docs flowCorpus (Text.pack user) (Text.pack name) (Multi FR) docs
-- cmd = {-createUsers >>-} cmdCorpus
env <- newDevEnvWith iniPath env <- newDevEnvWith iniPath
-- Better if we keep only one call to runCmdDev. -- Better if we keep only one call to runCmdDev.
_ <- if users == "0" _ <- if userCreate == "true"
then runCmdDev env createUsers then runCmdDev env createUsers
else pure 1 else pure 0 --(cs "false")
_ <- runCmdDev env cmdCorpus
_ <- runCmdDev env debatCorpus
{-
_ <- if corpusType == "csv"
then runCmdDev env csvCorpus
else if corpusType == "debat"
then runCmdDev env debatCorpus
else panic "corpusType unknown: try \"csv\" or \"debat\""
-}
pure () pure ()
...@@ -171,8 +171,6 @@ queryNgramsOnlyByNodeUser = [sql| ...@@ -171,8 +171,6 @@ queryNgramsOnlyByNodeUser = [sql|
GROUP BY nng.node_id, ng.terms GROUP BY nng.node_id, ng.terms
|] |]
------------------------------------------------------------------------ ------------------------------------------------------------------------
-- | TODO filter by language, database, any social field -- | TODO filter by language, database, any social field
getNodesByNgramsMaster :: UserCorpusId -> MasterCorpusId -> Cmd err (Map Text (Set NodeId)) getNodesByNgramsMaster :: UserCorpusId -> MasterCorpusId -> Cmd err (Map Text (Set NodeId))
...@@ -183,10 +181,10 @@ selectNgramsByNodeMaster :: UserCorpusId -> MasterCorpusId -> Cmd err [(NodeId, ...@@ -183,10 +181,10 @@ selectNgramsByNodeMaster :: UserCorpusId -> MasterCorpusId -> Cmd err [(NodeId,
selectNgramsByNodeMaster ucId mcId = runPGSQuery selectNgramsByNodeMaster ucId mcId = runPGSQuery
queryNgramsByNodeMaster queryNgramsByNodeMaster
( ucId ( ucId
, nodeTypeId NodeDocument , nodeTypeId NodeDocument
, ngramsTypeId NgramsTerms , ngramsTypeId NgramsTerms
, mcId , mcId
, nodeTypeId NodeDocument , nodeTypeId NodeDocument
, ngramsTypeId NgramsTerms , ngramsTypeId NgramsTerms
) )
......
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