]> Git — Sourcephile - gargantext.git/blob - bin/gargantext-import/Main.hs
[METRICS] FACTO
[gargantext.git] / bin / gargantext-import / Main.hs
1 {-|
2 Module : Main.hs
3 Description : Gargantext Import Corpus
4 Copyright : (c) CNRS, 2017-Present
5 License : AGPL + CECILL v3
6 Maintainer : team@gargantext.org
7 Stability : experimental
8 Portability : POSIX
9
10 Import a corpus binary.
11
12 -}
13
14 {-# LANGUAGE NoImplicitPrelude #-}
15 {-# LANGUAGE OverloadedStrings #-}
16 {-# LANGUAGE FlexibleContexts #-}
17 {-# LANGUAGE RankNTypes #-}
18 {-# LANGUAGE Strict #-}
19
20 module Main where
21
22 import Prelude (read)
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)
39
40 main :: IO ()
41 main = do
42 [userCreate, user, name, iniPath, limit, corpusPath] <- getArgs
43
44 --{-
45 let createUsers :: Cmd GargError Int64
46 createUsers = insertUsersDemo
47
48 let
49 --tt = (Unsupervised EN 6 0 Nothing)
50 tt = (Multi EN)
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
54 {-
55 let debatCorpus :: forall m. FlowCmdM DevEnv GargError m => m CorpusId
56 debatCorpus = do
57 docs <- liftIO ( splitEvery 500
58 <$> take (read limit :: Int)
59 <$> readFile corpusPath
60 :: IO [[GrandDebatReference ]]
61 )
62 flowCorpus (Text.pack user) (Text.pack name) (Multi FR) (map (map toHyperdataDocument) docs)
63 --}
64
65
66 withDevEnv iniPath $ \env -> do
67 _ <- if userCreate == "true"
68 then runCmdDev env createUsers
69 else pure 0 --(cs "false")
70
71 _ <- runCmdDev env cmd
72 {-
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\""
78 -}
79 pure ()