]> Git — Sourcephile - gargantext.git/blob - bin/gargantext-import/Main.hs
Merge branch 'dev-phylo' of https://gitlab.iscpif.fr/gargantext/haskell-gargantext...
[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 Strict #-}
15
16 module Main where
17
18 import Control.Exception (finally)
19 import Data.Either
20 import Data.Text (Text)
21 import Prelude (read)
22 import System.Environment (getArgs)
23 import qualified Data.Text as Text
24
25 import Gargantext.API.Dev (withDevEnv, runCmdDev)
26 import Gargantext.API.Admin.EnvTypes (DevEnv(..))
27 import Gargantext.API.Node () -- instances
28 import Gargantext.API.Prelude (GargError)
29 import Gargantext.Core (Lang(..))
30 import Gargantext.Core.Types.Individu (User(..))
31 import Gargantext.Database.Action.Flow (FlowCmdM, flowCorpusFile, flowAnnuaire, TermType(..))
32 import Gargantext.Database.Query.Table.User (insertUsersDemo)
33 import Gargantext.Database.Admin.Types.Hyperdata (toHyperdataDocument)
34 import Gargantext.Database.Admin.Types.Node (CorpusId)
35 import Gargantext.Database.Prelude (Cmd)
36 import Gargantext.Prelude
37 import Gargantext.Core.Text.Corpus.Parsers (FileFormat(..))
38
39 main :: IO ()
40 main = do
41 [fun, user, name, iniPath, limit, corpusPath] <- getArgs
42
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 = CsvGargV3 -- CsvHal --WOS
52 corpus :: forall m. FlowCmdM DevEnv GargError m => m CorpusId
53 corpus = flowCorpusFile (UserName $ cs user) (Left (cs name :: Text)) (read limit :: Int) tt format corpusPath
54
55 corpusCsvHal :: forall m. FlowCmdM DevEnv GargError m => m CorpusId
56 corpusCsvHal = flowCorpusFile (UserName $ cs user) (Left (cs name :: Text)) (read limit :: Int) tt CsvHal corpusPath
57
58 annuaire :: forall m. FlowCmdM DevEnv GargError m => m CorpusId
59 annuaire = flowAnnuaire (UserName $ cs user) (Left "Annuaire") (Multi EN) corpusPath
60
61 {-
62 let debatCorpus :: forall m. FlowCmdM DevEnv GargError m => m CorpusId
63 debatCorpus = do
64 docs <- liftIO ( splitEvery 500
65 <$> take (read limit :: Int)
66 <$> readFile corpusPath
67 :: IO [[GrandDebatReference ]]
68 )
69 flowCorpus (Text.pack user) (Text.pack name) (Multi FR) (map (map toHyperdataDocument) docs)
70 --}
71
72 withDevEnv iniPath $ \env -> do
73 _ <- if fun == "users"
74 then runCmdDev env createUsers
75 else pure 0 --(cs "false")
76
77 _ <- if fun == "corpus"
78 then runCmdDev env corpus
79 else pure 0 --(cs "false")
80
81 _ <- if fun == "corpusCsvHal"
82 then runCmdDev env corpusCsvHal
83 else pure 0 --(cs "false")
84
85 _ <- if fun == "annuaire"
86 then runCmdDev env annuaire
87 else pure 0
88 {-
89 _ <- if corpusType == "csv"
90 then runCmdDev env csvCorpus
91 else if corpusType == "debat"
92 then runCmdDev env debatCorpus
93 else panic "corpusType unknown: try \"csv\" or \"debat\""
94 -}
95 pure ()