]> Git — Sourcephile - gargantext.git/blob - src/Gargantext/Database/Node/Document/Add.hs
[Database] Refactor functions accessing the database
[gargantext.git] / src / Gargantext / Database / Node / Document / Add.hs
1 {-|
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
8 Portability : POSIX
9
10 Add Documents/Contact to a Corpus/Annuaire.
11
12 -}
13 ------------------------------------------------------------------------
14 {-# LANGUAGE DeriveDataTypeable #-}
15 {-# LANGUAGE DeriveGeneric #-}
16 {-# LANGUAGE FlexibleInstances #-}
17 {-# LANGUAGE NoImplicitPrelude #-}
18 {-# LANGUAGE OverloadedStrings #-}
19 {-# LANGUAGE QuasiQuotes #-}
20 {-# LANGUAGE RankNTypes #-}
21 {-# LANGUAGE TypeSynonymInstances #-}
22 ------------------------------------------------------------------------
23 module Gargantext.Database.Node.Document.Add where
24
25
26 import Data.ByteString.Internal (ByteString)
27 import Data.Typeable (Typeable)
28 import Database.PostgreSQL.Simple (Query, Only(..))
29 import Database.PostgreSQL.Simple.SqlQQ
30 import Database.PostgreSQL.Simple.ToField (toField)
31 import Database.PostgreSQL.Simple.ToRow (ToRow(..))
32 import Database.PostgreSQL.Simple.Types (Values(..), QualifiedIdentifier(..))
33
34 import Data.Text (Text)
35
36 import Gargantext.Database.Utils (Cmd, runPGSQuery, formatPGSQuery)
37 import Gargantext.Database.Types.Node
38 import Gargantext.Prelude
39
40 import GHC.Generics (Generic)
41 ---------------------------------------------------------------------------
42
43 type ParentId = Int
44
45 add :: ParentId -> [NodeId] -> Cmd err [Only Int]
46 add pId ns = runPGSQuery queryAdd (Only $ Values fields inputData)
47 where
48 fields = map (\t-> QualifiedIdentifier Nothing t) inputSqlTypes
49 inputData = prepare pId ns
50
51 add_debug :: ParentId -> [NodeId] -> Cmd err ByteString
52 add_debug pId ns = formatPGSQuery queryAdd (Only $ Values fields inputData)
53 where
54 fields = map (\t-> QualifiedIdentifier Nothing t) inputSqlTypes
55 inputData = prepare pId ns
56
57
58
59 -- | Input Tables: types of the tables
60 inputSqlTypes :: [Text]
61 inputSqlTypes = ["int4","int4","bool","bool"]
62
63 -- | SQL query to add documents
64 -- TODO return id of added documents only
65 queryAdd :: Query
66 queryAdd = [sql|
67 WITH input_rows(node1_id,node2_id, favorite, delete) AS (?)
68 INSERT INTO nodes_nodes (node1_id, node2_id, favorite, delete)
69 SELECT * FROM input_rows
70 ON CONFLICT (node1_id, node2_id) DO NOTHING -- on unique index
71 RETURNING 1
72 ;
73 |]
74
75 prepare :: ParentId -> [NodeId] -> [InputData]
76 prepare pId ns = map (\nId -> InputData pId nId False False) ns
77
78 ------------------------------------------------------------------------
79 -- * Main Types used
80
81
82 data InputData = InputData { inNode1_id :: NodeId
83 , inNode2_id :: NodeId
84 , inNode_fav :: Bool
85 , inNode_del :: Bool
86 } deriving (Show, Generic, Typeable)
87
88 instance ToRow InputData where
89 toRow inputData = [ toField (inNode1_id inputData)
90 , toField (inNode2_id inputData)
91 , toField (inNode_fav inputData)
92 , toField (inNode_del inputData)
93 ]
94