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