2 Module : Gargantext.Database.Node.Document.Add
3 Description : Importing context of texts (documents)
4 Copyright : (c) CNRS, 2017-Present
5 License : AGPL + CECILL v3
6 Maintainer : team@gargantext.org
7 Stability : experimental
10 Add Documents/Contact to a Corpus/Annuaire.
13 ------------------------------------------------------------------------
14 {-# LANGUAGE DeriveDataTypeable #-}
15 {-# LANGUAGE QuasiQuotes #-}
16 {-# LANGUAGE TypeSynonymInstances #-}
18 ------------------------------------------------------------------------
19 module Gargantext.Database.Query.Table.Node.Document.Add
22 import Data.ByteString.Internal (ByteString)
23 import Data.Text (Text)
24 import Database.PostgreSQL.Simple (Query, Only(..))
25 import Database.PostgreSQL.Simple.SqlQQ
26 import Database.PostgreSQL.Simple.ToField (toField)
27 import Database.PostgreSQL.Simple.ToRow (ToRow(..))
28 import Database.PostgreSQL.Simple.Types (Values(..), QualifiedIdentifier(..))
29 import GHC.Generics (Generic)
30 import Gargantext.Database.Admin.Types.Node
31 import Gargantext.Database.Prelude (Cmd, runPGSQuery, formatPGSQuery)
32 import Gargantext.Prelude
34 ---------------------------------------------------------------------------
36 add :: CorpusId -> [ContextId] -> Cmd err [Only Int]
37 add pId ns = runPGSQuery queryAdd (Only $ Values fields inputData)
39 fields = map (\t-> QualifiedIdentifier Nothing t) inputSqlTypes
40 inputData = prepare pId ns
42 add_debug :: CorpusId -> [ContextId] -> Cmd err ByteString
43 add_debug pId ns = formatPGSQuery queryAdd (Only $ Values fields inputData)
45 fields = map (\t-> QualifiedIdentifier Nothing t) inputSqlTypes
46 inputData = prepare pId ns
49 -- | Input Tables: types of the tables
50 inputSqlTypes :: [Text]
51 inputSqlTypes = ["int4","int4","int4","int4"]
53 -- | SQL query to add documents
54 -- TODO return id of added documents only
57 WITH input_rows(node_id,context_id,score,category) AS (?)
58 INSERT INTO nodes_contexts (node_id, context_id,score,category)
59 SELECT * FROM input_rows
60 ON CONFLICT (node_id, context_id) DO NOTHING -- on unique index
65 prepare :: ParentId -> [ContextId] -> [InputData]
66 prepare pId ns = map (\cId -> InputData pId cId) ns
68 ------------------------------------------------------------------------
71 data InputData = InputData { inNode_id :: NodeId
72 , inContext_id :: ContextId
73 } deriving (Show, Generic, Typeable)
75 instance ToRow InputData where
76 toRow inputData = [ toField (inNode_id inputData)
77 , toField (inContext_id inputData)