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.NodesNodes
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 new1.node_id, lists.id, nnn.ngrams_id, nnn.ngrams_type, count(*) as weight
40 INNER JOIN contexts doc ON doc.id = new1.context_id
41 INNER JOIN nodes lists ON lists.parent_id = new1.node_id
42 INNER JOIN context_node_ngrams nnn ON nnn.context_id = doc.id
43 WHERE lists.id in (?, lists.id)
44 AND lists.typename = ?
45 GROUP BY new1.node_id, lists.id, nnn.ngrams_id, nnn.ngrams_type
46 ON CONFLICT (node1_id, node2_id, ngrams_id, ngrams_type)
47 DO UPDATE set weight = node_node_ngrams.weight + excluded.weight
53 DROP TRIGGER IF EXISTS trigger_insert_count ON nodes_contexts;
54 CREATE TRIGGER trigger_insert_count AFTER INSERT ON nodes_contexts
55 REFERENCING NEW TABLE AS NEW
57 EXECUTE PROCEDURE set_insert_count();
61 triggerUpdateAdd :: MasterListId -> Cmd err Int64
62 triggerUpdateAdd lId = execPGSQuery query (lId, nodeTypeId NodeList)
66 CREATE OR REPLACE FUNCTION set_update_ngrams_add() RETURNS trigger AS $$
68 UPDATE node_node_ngrams nnn0 SET weight = weight + d.fix_count
69 FROM ( SELECT lists.parent_id AS node1_id
70 , lists.id AS node2_id
71 , cnn.ngrams_id AS ngrams_id
72 , cnn.ngrams_type AS ngrams_type
73 , count(*) AS fix_count
75 INNER JOIN contexts doc ON doc.id = new1.context_id
76 INNER JOIN nodes lists ON new1.node_id = lists.parent_id
77 INNER JOIN context_node_ngrams cnn ON cnn.context_id = doc.id
78 WHERE lists.id in (?, lists.id) -- (masterList_id, userLists)
79 AND lists.typename = ?
80 GROUP BY node1_id, node2_id, ngrams_id, ngrams_type
82 WHERE nnn0.node1_id = d.node1_id
83 AND nnn0.node2_id = d.node2_id
84 AND nnn0.ngrams_id = d.ngrams_id
85 AND nnn0.ngrams_type = d.ngrams_type
91 DROP trigger IF EXISTS trigger_count_update_add on nodes_contexts;
92 CREATE TRIGGER trigger_count_update_add AFTER UPDATE on nodes_contexts
93 REFERENCING OLD TABLE AS OLD
96 WHEN (OLD.category <= 0 AND NEW.category >= 1)
97 EXECUTE PROCEDURE set_update_ngrams_add();
101 triggerUpdateDel :: MasterListId -> Cmd err Int64
102 triggerUpdateDel lId = execPGSQuery query (lId, nodeTypeId NodeList)
106 CREATE OR REPLACE FUNCTION set_update_ngrams_count_del() RETURNS trigger AS $$
108 UPDATE node_node_ngrams nnn0 SET weight = weight - d.fix_count
109 FROM ( SELECT lists.parent_id AS node1_id
110 , lists.id AS node2_id
111 , cnn.ngrams_id AS ngrams_id
112 , cnn.ngrams_type AS ngrams_type
113 , count(*) AS fix_count
115 INNER JOIN contexts doc ON doc.id = new1.context_id
116 INNER JOIN nodes lists ON new1.node_id = lists.parent_id
117 INNER JOIN context_node_ngrams cnn ON cnn.context_id = doc.id
118 WHERE lists.id in (?, lists.id) -- (masterList_id, userLists)
119 AND lists.typename = ?
120 GROUP BY node1_id, node2_id, ngrams_id, ngrams_type
122 WHERE nnn0.node1_id = d.node1_id
123 AND nnn0.node2_id = d.node2_id
124 AND nnn0.ngrams_id = d.ngrams_id
125 AND nnn0.ngrams_type = d.ngrams_type
131 DROP TRIGGER IF EXISTS trigger_count_delete2 ON nodes_contexts;
132 CREATE TRIGGER trigger_count_delete2 AFTER UPDATE ON nodes_contexts
133 REFERENCING OLD TABLE AS OLD
136 WHEN (OLD.category >= 1 AND NEW.category <= 0)
137 EXECUTE PROCEDURE set_update_ngrams_count_del();
143 triggerDeleteCount :: MasterListId -> Cmd err Int64
144 triggerDeleteCount lId = execPGSQuery query (lId, toDBid NodeList)
148 CREATE OR REPLACE FUNCTION set_delete_count() RETURNS trigger AS $$
150 UPDATE context_node_ngrams SET weight = weight - d.delete_count
151 FROM ( SELECT lists.id as node_id
152 , old1.context_id as context_id
153 , nnn.ngrams_id as ngrams_id
154 , nnn.ngrams_type as ngrams_type
155 , count(*) as delete_count FROM OLD as old1
156 INNER JOIN contexts doc ON doc.id = old1.context_id
157 INNER JOIN nodes lists ON lists.parent_id = old1.node_id
158 INNER JOIN context_node_ngrams nnn ON nnn.context_id = doc.id
159 WHERE nnn.node_id in (?, lists.id)
160 AND lists.typename = ?
161 GROUP BY old1.context_id, lists.id, nnn.ngrams_id, nnn.ngrams_type
163 WHERE context_node_ngrams.context_id = d.context_id
164 AND context_node_ngrams.node_id = d.node_id
165 AND context_node_ngrams.ngrams_id = d.ngrams_id
166 AND context_node_ngrams.ngrams_type = d.ngrams_type
172 -- DROP trigger trigger_delete_count on nodes_nodes;
173 CREATE TRIGGER trigger_delete_count AFTER DELETE on nodes_contexts
174 REFERENCING OLD TABLE AS OLD
176 EXECUTE PROCEDURE set_delete_count();
182 triggerCoocInsert :: MasterListId -> Cmd err Int64
183 triggerCoocInsert lid = execPGSQuery query ( lid
184 -- , nodeTypeId NodeCorpus
185 -- , nodeTypeId NodeDocument
186 -- , nodeTypeId NodeList
187 , toDBid CandidateTerm
188 , toDBid CandidateTerm
193 CREATE OR REPLACE FUNCTION nodes_nodes_set_cooc() RETURNS trigger AS $$
195 IF pg_trigger_depth() <> 1 THEN
198 IF TG_OP = 'INSERT' THEN
199 INSERT INTO node_nodengrams_nodengrams (node_id, node_ngrams1_id, node_ngrams2_id, weight)
200 WITH input(corpus_id, nn1, nn2, weight) AS (
201 SELECT new1.node1_id, nn1.id, nn2.id, count(*) from NEW as new1
202 INNER JOIN node_ngrams nn1
203 ON nn1.node_id = ? -- COALESCE(?,?) --(masterList, userList)
204 INNER JOIN node_ngrams nn2
205 ON nn2.node_id = nn1.node_id
207 INNER JOIN node_node_ngrams2 nnn1
208 ON nnn1.node_id = new1.node2_id
210 INNER JOIN node_node_ngrams2 nnn2
211 ON nnn2.node_id = new1.node2_id
213 WHERE nnn1.nodengrams_id = nn1.id
214 AND nnn2.nodengrams_id = nn2.id
216 AND nn1.node_subtype >= ?
217 AND nn2.node_subtype >= ?
218 GROUP BY new1.node1_id, nn1.id, nn2.id
220 SELECT * from input where weight >= 1
222 ON CONFLICT (node_id, node_ngrams1_id, node_ngrams2_id)
223 DO UPDATE set weight = node_nodengrams_nodengrams.weight + excluded.weight
231 -- DROP trigger trigger_cooc on node_node_ngrams2;
233 CREATE TRIGGER trigger_cooc_insert AFTER INSERT on nodes_nodes
234 REFERENCING NEW TABLE AS NEW
236 EXECUTE PROCEDURE nodes_nodes_set_cooc();