]> Git — Sourcephile - gargantext.git/blob - bin/gargantext-import/Main.hs
[FIX] Build.
[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 Data.Either
23 import Prelude (read)
24 import Control.Exception (finally)
25 import Gargantext.Prelude
26 import Gargantext.Database.Flow (FlowCmdM, flowCorpusFile)
27 import Gargantext.Text.Corpus.Parsers (FileFormat(..))
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 -- (GargError)
34 import Gargantext.API.Node () -- instances
35 import Gargantext.API.Settings (withDevEnv, runCmdDev, DevEnv)
36 import System.Environment (getArgs)
37 --import Gargantext.Text.Corpus.Parsers.GrandDebat (readFile, GrandDebatReference(..))
38 import Data.Text (Text)
39 import qualified Data.Text as Text
40 import Control.Monad.IO.Class (liftIO)
41
42 main :: IO ()
43 main = do
44 [userCreate, user, name, iniPath, limit, corpusPath] <- getArgs
45
46 --{-
47 let createUsers :: Cmd GargError Int64
48 createUsers = insertUsersDemo
49
50 let
51 --tt = (Unsupervised EN 6 0 Nothing)
52 tt = (Multi EN)
53 format = WOS -- CsvGargV3
54 cmd :: forall m. FlowCmdM DevEnv GargError m => m CorpusId
55 cmd = flowCorpusFile (cs user) (Left (cs name :: Text)) (read limit :: Int) tt format corpusPath
56 {-
57 let debatCorpus :: forall m. FlowCmdM DevEnv GargError m => m CorpusId
58 debatCorpus = do
59 docs <- liftIO ( splitEvery 500
60 <$> take (read limit :: Int)
61 <$> readFile corpusPath
62 :: IO [[GrandDebatReference ]]
63 )
64 flowCorpus (Text.pack user) (Text.pack name) (Multi FR) (map (map toHyperdataDocument) docs)
65 --}
66
67
68 withDevEnv iniPath $ \env -> do
69 _ <- if userCreate == "true"
70 then runCmdDev env createUsers
71 else pure 0 --(cs "false")
72
73 _ <- runCmdDev env cmd
74 {-
75 _ <- if corpusType == "csv"
76 then runCmdDev env csvCorpus
77 else if corpusType == "debat"
78 then runCmdDev env debatCorpus
79 else panic "corpusType unknown: try \"csv\" or \"debat\""
80 -}
81 pure ()