2 Module : Gargantext.Database.Triggers
3 Description : Triggers configuration
4 Copyright : (c) CNRS, 2017-Present
5 License : AGPL + CECILL v3
6 Maintainer : team@gargantext.org
7 Stability : experimental
10 Ngrams by node enable contextual metrics.
14 {-# LANGUAGE QuasiQuotes #-}
15 {-# LANGUAGE NoImplicitPrelude #-}
16 {-# LANGUAGE OverloadedStrings #-}
17 {-# LANGUAGE RankNTypes #-}
19 module Gargantext.Database.Triggers
22 import Database.PostgreSQL.Simple.SqlQQ (sql)
23 -- import Database.PostgreSQL.Simple.Types (Values(..), QualifiedIdentifier(..))
24 import Gargantext.Database.Config (nodeTypeId)
25 import Gargantext.Database.Types.Node -- (ListId, CorpusId, NodeId)
26 import Gargantext.Database.Utils (Cmd, runPGSQuery)
27 import Gargantext.Prelude
28 import qualified Database.PostgreSQL.Simple as DPS
30 ------------------------------------------------------------------------
32 type MasterListId = ListId
34 insertOccsUpdates :: UserCorpusId -> MasterListId -> Cmd err [DPS.Only Int]
35 insertOccsUpdates cId lId = runPGSQuery query (cId, lId, nodeTypeId NodeList, nodeTypeId NodeDocument)
39 INSERT INTO node_node_ngrams (node1_id, node2_id, ngrams_id, ngrams_type, weight)
40 SELECT nn.node1_id, lists.id, nnn.ngrams_id, count(*), 1 -- type of score
41 FROM node_node_ngrams nnn
42 INNER JOIN nodes_nodes nn ON nn.node2_id = nnn.node2_id
43 INNER JOIN nodes docs ON docs.id = nnn.node2_id
44 INNER JOIN nodes lists ON lists.parent_id = nn.node1_id
45 -- WHERE nn.node1_id = NEW.node1_id -- .node1_id -- corpus_id
46 WHERE nn.node1_id = ? -- .node1_id -- corpus_id
47 AND nnn.node1_id in (?, lists.id) -- (masterList_id, userLists)
48 AND lists.typename = ?
50 GROUP BY nn.node1_id, lists.id, nnn.ngrams_id
51 ON CONFLICT (node1_id, node2_id, ngrams_id, ngrams_type)
52 DO UPDATE SET weight = excluded.weight +1; -- TOCHECK
57 triggerOccsUpdates :: CorpusId -> ListId -> Cmd err [DPS.Only Int]
58 triggerOccsUpdates cId lId = runPGSQuery query (cId, lId, nodeTypeId NodeList, nodeTypeId NodeDocument)
62 drop trigger trigger_occs on nodes_nodes;
63 CREATE OR REPLACE FUNCTION occs_update() RETURNS trigger AS
66 IF TG_OP = 'UPDATE' THEN
67 INSERT INTO node_node_ngrams (node1_id, node2_id, ngrams_id, ngrams_type, weight)
68 -- TODO edge_type instead of ngrams_type
69 SELECT nn.node1_id, lists.id, nnn.ngrams_id, count(*), 1 -- type of score
70 FROM node_node_ngrams nnn
71 INNER JOIN nodes_nodes nn ON nn.node2_id = nnn.node2_id
72 INNER JOIN nodes docs ON docs.id = nnn.node2_id
73 INNER JOIN nodes lists ON lists.parent_id = nn.node1_id
74 -- WHERE nn.node1_id = NEW.node1_id -- .node1_id -- corpus_id
75 WHERE nn.node1_id = ? -- .node1_id -- corpus_id
76 AND nnn.node1_id in (?, lists.id) -- (masterList_id, userLists)
77 AND lists.typename = ?
79 GROUP BY nn.node1_id, lists.id, nnn.ngrams_id
80 ON CONFLICT (node1_id, node2_id, ngrams_id, ngrams_type)
81 DO UPDATE SET weight = excluded.weight;
87 CREATE TRIGGER trigger_occs
88 AFTER UPDATE ON nodes_nodes
89 REFERENCING NEW TABLE AS NEW
91 EXECUTE PROCEDURE occs_update();
93 update nodes_nodes SET node1_id = node1_id;