]> Git — Sourcephile - gargantext.git/blob - bin/gargantext-import/Main.hs
merge done
[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 Servant (ServantErr)
25 import Gargantext.Prelude
26 import Gargantext.Database.Flow (FlowCmdM, flowCorpusFile)
27 import Gargantext.Text.Parsers (FileFormat(CsvHalFormat))
28 import Gargantext.Database.Utils (Cmd, )
29 import Gargantext.Database.Types.Node (CorpusId, toHyperdataDocument)
30 import Gargantext.Database.Schema.User (insertUsersDemo)
31 import Gargantext.Text.Terms (TermType(..))
32 import Gargantext.Core (Lang(..))
33 import Gargantext.API.Node () -- instances
34 import Gargantext.API.Settings (withDevEnv, runCmdDev, DevEnv)
35 import System.Environment (getArgs)
36 --import Gargantext.Text.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 ServantErr Int64
46 createUsers = insertUsersDemo
47
48 let
49 --tt = (Unsupervised EN 5 1 Nothing)
50 tt = (Mono EN)
51 cmd :: forall m. FlowCmdM DevEnv ServantErr m => m CorpusId
52 cmd = flowCorpusFile (cs user) (cs name) (read limit :: Int) tt CsvHalFormat corpusPath
53 {-
54 let debatCorpus :: forall m. FlowCmdM DevEnv ServantErr m => m CorpusId
55 debatCorpus = do
56 docs <- liftIO ( splitEvery 500
57 <$> take (read limit :: Int)
58 <$> readFile corpusPath
59 :: IO [[GrandDebatReference ]]
60 )
61 flowCorpus (Text.pack user) (Text.pack name) (Multi FR) (map (map toHyperdataDocument) docs)
62 --}
63
64
65 withDevEnv iniPath $ \env -> do
66 _ <- if userCreate == "true"
67 then runCmdDev env createUsers
68 else pure 0 --(cs "false")
69
70 _ <- runCmdDev env cmd
71 {-
72 _ <- if corpusType == "csv"
73 then runCmdDev env csvCorpus
74 else if corpusType == "debat"
75 then runCmdDev env debatCorpus
76 else panic "corpusType unknown: try \"csv\" or \"debat\""
77 -}
78 pure ()