2 Module : Gargantext.Database.Triggers.NodesNodes
3 Description : Triggers configuration
4 Copyright : (c) CNRS, 2017-Present
5 License : AGPL + CECILL v3
6 Maintainer : team@gargantext.org
7 Stability : experimental
10 Triggers on NodesNodes table.
14 {-# LANGUAGE QuasiQuotes #-}
16 module Gargantext.Database.Admin.Trigger.NodesContexts
19 import Database.PostgreSQL.Simple.SqlQQ (sql)
20 import Gargantext.Core
21 import Gargantext.Database.Admin.Config
22 import Gargantext.Database.Admin.Types.Node -- (ListId, CorpusId, NodeId)
23 import Gargantext.Database.Prelude (Cmd, execPGSQuery)
24 import Gargantext.Prelude
25 import qualified Database.PostgreSQL.Simple as DPS
27 type MasterListId = ListId
29 triggerInsertCount :: MasterListId -> Cmd err Int64
30 triggerInsertCount lId = execPGSQuery query (lId, nodeTypeId NodeList)
34 CREATE OR REPLACE FUNCTION set_insert_count() RETURNS trigger
37 INSERT INTO node_node_ngrams (node1_id, node2_id, ngrams_id, ngrams_type, weight)
38 SELECT lists.parent_id
44 INNER JOIN contexts doc ON doc.id = new1.context_id
45 INNER JOIN nodes lists ON lists.parent_id = lists.parent_id
46 INNER JOIN context_node_ngrams cnn ON cnn.context_id = doc.id
47 WHERE lists.id in (?, lists.id)
48 AND lists.typename = ?
49 GROUP BY lists.parent_id, lists.id, cnn.ngrams_id, cnn.ngrams_type
50 ON CONFLICT (node1_id, node2_id, ngrams_id, ngrams_type)
51 DO UPDATE set weight = node_node_ngrams.weight + excluded.weight
57 DROP TRIGGER IF EXISTS trigger_insert_count ON nodes_contexts;
58 CREATE TRIGGER trigger_insert_count AFTER INSERT ON nodes_contexts
59 REFERENCING NEW TABLE AS NEW
61 EXECUTE PROCEDURE set_insert_count();
65 triggerUpdateAdd :: MasterListId -> Cmd err Int64
66 triggerUpdateAdd lId = execPGSQuery query (lId, nodeTypeId NodeList)
70 CREATE OR REPLACE FUNCTION set_update_ngrams_add() RETURNS trigger AS $$
72 UPDATE node_node_ngrams nnn0 SET weight = weight + d.fix_count
73 FROM ( SELECT lists.parent_id AS node1_id
74 , lists.id AS node2_id
75 , cnn.ngrams_id AS ngrams_id
76 , cnn.ngrams_type AS ngrams_type
77 , count(*) AS fix_count
79 INNER JOIN contexts doc ON doc.id = new1.context_id
80 INNER JOIN nodes lists ON new1.node_id = lists.parent_id
81 INNER JOIN context_node_ngrams cnn ON cnn.context_id = doc.id
82 WHERE lists.id in (?, lists.id) -- (masterList_id, userLists)
83 AND lists.typename = ?
84 GROUP BY node1_id, node2_id, ngrams_id, ngrams_type
86 WHERE nnn0.node1_id = d.node1_id
87 AND nnn0.node2_id = d.node2_id
88 AND nnn0.ngrams_id = d.ngrams_id
89 AND nnn0.ngrams_type = d.ngrams_type
95 DROP trigger IF EXISTS trigger_count_update_add on nodes_contexts;
96 CREATE TRIGGER trigger_count_update_add AFTER UPDATE on nodes_contexts
97 REFERENCING OLD TABLE AS OLD
100 WHEN (OLD.category <= 0 AND NEW.category >= 1)
101 EXECUTE PROCEDURE set_update_ngrams_add();
105 triggerUpdateDel :: MasterListId -> Cmd err Int64
106 triggerUpdateDel lId = execPGSQuery query (lId, nodeTypeId NodeList)
110 CREATE OR REPLACE FUNCTION set_update_ngrams_count_del() RETURNS trigger AS $$
112 UPDATE node_node_ngrams nnn0 SET weight = weight - d.fix_count
113 FROM ( SELECT lists.parent_id AS node1_id
114 , lists.id AS node2_id
115 , cnn.ngrams_id AS ngrams_id
116 , cnn.ngrams_type AS ngrams_type
117 , count(*) AS fix_count
119 INNER JOIN contexts doc ON doc.id = new1.context_id
120 INNER JOIN nodes lists ON new1.node_id = lists.parent_id
121 INNER JOIN context_node_ngrams cnn ON cnn.context_id = doc.id
122 WHERE lists.id in (?, lists.id) -- (masterList_id, userLists)
123 AND lists.typename = ?
124 GROUP BY node1_id, node2_id, ngrams_id, ngrams_type
126 WHERE nnn0.node1_id = d.node1_id
127 AND nnn0.node2_id = d.node2_id
128 AND nnn0.ngrams_id = d.ngrams_id
129 AND nnn0.ngrams_type = d.ngrams_type
135 DROP TRIGGER IF EXISTS trigger_count_delete2 ON nodes_contexts;
136 CREATE TRIGGER trigger_count_delete2 AFTER UPDATE ON nodes_contexts
137 REFERENCING OLD TABLE AS OLD
140 WHEN (OLD.category >= 1 AND NEW.category <= 0)
141 EXECUTE PROCEDURE set_update_ngrams_count_del();
147 triggerDeleteCount :: MasterListId -> Cmd err Int64
148 triggerDeleteCount lId = execPGSQuery query (lId, toDBid NodeList)
152 CREATE OR REPLACE FUNCTION set_delete_count() RETURNS trigger AS $$
154 UPDATE context_node_ngrams SET weight = weight - d.delete_count
155 FROM ( SELECT lists.id as node_id
156 , old1.context_id as context_id
157 , nnn.ngrams_id as ngrams_id
158 , nnn.ngrams_type as ngrams_type
159 , count(*) as delete_count FROM OLD as old1
160 INNER JOIN contexts doc ON doc.id = old1.context_id
161 INNER JOIN nodes lists ON lists.parent_id = old1.node_id
162 INNER JOIN context_node_ngrams nnn ON nnn.context_id = doc.id
163 WHERE nnn.node_id in (?, lists.id)
164 AND lists.typename = ?
165 GROUP BY old1.context_id, lists.id, nnn.ngrams_id, nnn.ngrams_type
167 WHERE context_node_ngrams.context_id = d.context_id
168 AND context_node_ngrams.node_id = d.node_id
169 AND context_node_ngrams.ngrams_id = d.ngrams_id
170 AND context_node_ngrams.ngrams_type = d.ngrams_type
176 -- DROP trigger trigger_delete_count on nodes_nodes;
177 CREATE TRIGGER trigger_delete_count AFTER DELETE on nodes_contexts
178 REFERENCING OLD TABLE AS OLD
180 EXECUTE PROCEDURE set_delete_count();
186 triggerCoocInsert :: MasterListId -> Cmd err Int64
187 triggerCoocInsert lid = execPGSQuery query ( lid
188 -- , nodeTypeId NodeCorpus
189 -- , nodeTypeId NodeDocument
190 -- , nodeTypeId NodeList
191 , toDBid CandidateTerm
192 , toDBid CandidateTerm
197 CREATE OR REPLACE FUNCTION nodes_nodes_set_cooc() RETURNS trigger AS $$
199 IF pg_trigger_depth() <> 1 THEN
202 IF TG_OP = 'INSERT' THEN
203 INSERT INTO node_nodengrams_nodengrams (node_id, node_ngrams1_id, node_ngrams2_id, weight)
204 WITH input(corpus_id, nn1, nn2, weight) AS (
205 SELECT new1.node1_id, nn1.id, nn2.id, count(*) from NEW as new1
206 INNER JOIN node_ngrams nn1
207 ON nn1.node_id = ? -- COALESCE(?,?) --(masterList, userList)
208 INNER JOIN node_ngrams nn2
209 ON nn2.node_id = nn1.node_id
211 INNER JOIN node_node_ngrams2 nnn1
212 ON nnn1.node_id = new1.node2_id
214 INNER JOIN node_node_ngrams2 nnn2
215 ON nnn2.node_id = new1.node2_id
217 WHERE nnn1.nodengrams_id = nn1.id
218 AND nnn2.nodengrams_id = nn2.id
220 AND nn1.node_subtype >= ?
221 AND nn2.node_subtype >= ?
222 GROUP BY new1.node1_id, nn1.id, nn2.id
224 SELECT * from input where weight >= 1
226 ON CONFLICT (node_id, node_ngrams1_id, node_ngrams2_id)
227 DO UPDATE set weight = node_nodengrams_nodengrams.weight + excluded.weight
235 -- DROP trigger trigger_cooc on node_node_ngrams2;
237 CREATE TRIGGER trigger_cooc_insert AFTER INSERT on nodes_nodes
238 REFERENCING NEW TABLE AS NEW
240 EXECUTE PROCEDURE nodes_nodes_set_cooc();