3 Description : Gargantext Import Corpus
4 Copyright : (c) CNRS, 2017-Present
5 License : AGPL + CECILL v3
6 Maintainer : team@gargantext.org
7 Stability : experimental
10 Import a corpus binary.
14 {-# LANGUAGE NoImplicitPrelude #-}
15 {-# LANGUAGE OverloadedStrings #-}
16 {-# LANGUAGE FlexibleContexts #-}
17 {-# LANGUAGE RankNTypes #-}
18 {-# LANGUAGE Strict #-}
23 import Control.Exception (finally)
24 import Gargantext.Prelude
25 import Gargantext.Database.Flow (FlowCmdM, flowCorpusFile)
26 import Gargantext.Text.Corpus.Parsers (FileFormat(..))
27 import Gargantext.Database.Utils (Cmd, )
28 import Gargantext.Database.Types.Node (CorpusId, toHyperdataDocument)
29 import Gargantext.Database.Schema.User (insertUsersDemo)
30 import Gargantext.Text.Terms (TermType(..))
31 import Gargantext.Core (Lang(..))
32 import Gargantext.API -- (GargError)
33 import Gargantext.API.Node () -- instances
34 import Gargantext.API.Settings (withDevEnv, runCmdDev, DevEnv)
35 import System.Environment (getArgs)
36 --import Gargantext.Text.Corpus.Parsers.GrandDebat (readFile, GrandDebatReference(..))
37 import qualified Data.Text as Text
38 import Control.Monad.IO.Class (liftIO)
42 [userCreate, user, name, iniPath, limit, corpusPath] <- getArgs
45 let createUsers :: Cmd GargError Int64
46 createUsers = insertUsersDemo
49 --tt = (Unsupervised EN 6 0 Nothing)
51 format = WOS -- CsvGargV3
52 cmd :: forall m. FlowCmdM DevEnv GargError m => m CorpusId
53 cmd = flowCorpusFile (cs user) (cs name) (read limit :: Int) tt format corpusPath
55 let debatCorpus :: forall m. FlowCmdM DevEnv GargError m => m CorpusId
57 docs <- liftIO ( splitEvery 500
58 <$> take (read limit :: Int)
59 <$> readFile corpusPath
60 :: IO [[GrandDebatReference ]]
62 flowCorpus (Text.pack user) (Text.pack name) (Multi FR) (map (map toHyperdataDocument) docs)
66 withDevEnv iniPath $ \env -> do
67 _ <- if userCreate == "true"
68 then runCmdDev env createUsers
69 else pure 0 --(cs "false")
71 _ <- runCmdDev env cmd
73 _ <- if corpusType == "csv"
74 then runCmdDev env csvCorpus
75 else if corpusType == "debat"
76 then runCmdDev env debatCorpus
77 else panic "corpusType unknown: try \"csv\" or \"debat\""