]> Git — Sourcephile - gargantext.git/blob - bin/gargantext-import/Main.hs
Merge branch 'dev' into dev-graph-explorer-gexf
[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, flowAnnuaire)
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.Types (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
41 main :: IO ()
42 main = do
43 [fun, user, name, iniPath, limit, corpusPath] <- getArgs
44
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 = CsvGargV3 -- CsvHal --WOS
54 corpus :: forall m. FlowCmdM DevEnv GargError m => m CorpusId
55 corpus = flowCorpusFile (cs user) (Left (cs name :: Text)) (read limit :: Int) tt format corpusPath
56
57 corpusCsvHal :: forall m. FlowCmdM DevEnv GargError m => m CorpusId
58 corpusCsvHal = flowCorpusFile (cs user) (Left (cs name :: Text)) (read limit :: Int) tt CsvHal corpusPath
59
60 annuaire :: forall m. FlowCmdM DevEnv GargError m => m CorpusId
61 annuaire = flowAnnuaire (cs user) (Left "Annuaire") (Multi EN) corpusPath
62
63
64 {-
65 let debatCorpus :: forall m. FlowCmdM DevEnv GargError m => m CorpusId
66 debatCorpus = do
67 docs <- liftIO ( splitEvery 500
68 <$> take (read limit :: Int)
69 <$> readFile corpusPath
70 :: IO [[GrandDebatReference ]]
71 )
72 flowCorpus (Text.pack user) (Text.pack name) (Multi FR) (map (map toHyperdataDocument) docs)
73 --}
74
75 withDevEnv iniPath $ \env -> do
76 _ <- if fun == "users"
77 then runCmdDev env createUsers
78 else pure 0 --(cs "false")
79
80 _ <- if fun == "corpus"
81 then runCmdDev env corpus
82 else pure 0 --(cs "false")
83
84 _ <- if fun == "corpusCsvHal"
85 then runCmdDev env corpusCsvHal
86 else pure 0 --(cs "false")
87
88
89 _ <- if fun == "annuaire"
90 then runCmdDev env annuaire
91 else pure 0
92 {-
93 _ <- if corpusType == "csv"
94 then runCmdDev env csvCorpus
95 else if corpusType == "debat"
96 then runCmdDev env debatCorpus
97 else panic "corpusType unknown: try \"csv\" or \"debat\""
98 -}
99 pure ()