2 Module : Gargantext.Database.Schema.NodeNgrams
3 Description : NodeNgram for Ngram indexation or Lists
4 Copyright : (c) CNRS, 2017-Present
5 License : AGPL + CECILL v3
6 Maintainer : team@gargantext.org
7 Stability : experimental
10 NodeNgram: relation between a Node and a Ngrams
12 if Node is a Document then it is indexing
13 if Node is a List then it is listing (either Stop, Candidate or Map)
17 {-# OPTIONS_GHC -fno-warn-orphans #-}
19 {-# LANGUAGE Arrows #-}
20 {-# LANGUAGE FlexibleInstances #-}
21 {-# LANGUAGE FunctionalDependencies #-}
22 {-# LANGUAGE GeneralizedNewtypeDeriving #-}
23 {-# LANGUAGE MultiParamTypeClasses #-}
24 {-# LANGUAGE NoImplicitPrelude #-}
25 {-# LANGUAGE OverloadedStrings #-}
26 {-# LANGUAGE QuasiQuotes #-}
27 {-# LANGUAGE RankNTypes #-}
28 {-# LANGUAGE TemplateHaskell #-}
32 module Gargantext.Database.Schema.NodeNgram where
34 import Data.ByteString (ByteString)
35 import Data.Text (Text)
36 import Debug.Trace (trace)
37 import Control.Lens.TH (makeLenses)
38 import Control.Monad (void)
39 import Data.Profunctor.Product.TH (makeAdaptorAndInstance)
40 import Database.PostgreSQL.Simple.Types (Values(..), QualifiedIdentifier(..))
41 import Database.PostgreSQL.Simple.SqlQQ (sql)
42 import Gargantext.Database.Utils (mkCmd, Cmd, execPGSQuery)
43 import Gargantext.Core.Types.Main (ListTypeId)
44 import Gargantext.Database.Types.Node (NodeId, ListId, NodeType(..))
45 import Gargantext.Database.Config (nodeTypeId, userMaster)
46 import Gargantext.Database.Schema.Node (pgNodeId)
47 import Gargantext.Database.Schema.Ngrams (NgramsTypeId, pgNgramsTypeId)
48 import Gargantext.Prelude
49 import Gargantext.Database.Utils (formatPGSQuery)
51 import qualified Database.PostgreSQL.Simple as DPS
54 data NodeNgramPoly node_id ngrams_id parent_id ngrams_type list_type weight
55 = NodeNgram { _nn_node_id :: node_id
56 , _nn_ngrams_id :: ngrams_id
57 , _nn_parent_id :: parent_id
59 , _nn_ngramsType :: ngrams_type
60 , _nn_listType :: list_type
61 , _nn_weight :: weight
68 (Maybe (Column PGInt4))
84 type NodeNgramReadNull =
86 (Column (Nullable PGInt4 ))
87 (Column (Nullable PGInt4 ))
88 (Column (Nullable PGInt4 ))
90 (Column (Nullable PGInt4 ))
91 (Column (Nullable PGInt4 ))
92 (Column (Nullable PGFloat8))
95 NodeNgramPoly NodeId Int (Maybe NgramsParentId) NgramsTypeId Int Double
97 newtype NgramsParentId = NgramsParentId Int
98 deriving (Show, Eq, Num)
100 pgNgramsParentId :: NgramsParentId -> Column PGInt4
101 pgNgramsParentId (NgramsParentId n) = pgInt4 n
103 $(makeAdaptorAndInstance "pNodeNgram" ''NodeNgramPoly)
104 makeLenses ''NodeNgramPoly
106 nodeNgramTable :: Table NodeNgramWrite NodeNgramRead
107 nodeNgramTable = Table "nodes_ngrams"
108 ( pNodeNgram NodeNgram
109 { _nn_node_id = required "node_id"
110 , _nn_ngrams_id = required "ngrams_id"
111 , _nn_parent_id = optional "parent_id"
112 , _nn_ngramsType = required "ngrams_type"
113 , _nn_listType = required "list_type"
114 , _nn_weight = required "weight"
118 queryNodeNgramTable :: Query NodeNgramRead
119 queryNodeNgramTable = queryTable nodeNgramTable
121 insertNodeNgrams :: [NodeNgram] -> Cmd err Int
122 insertNodeNgrams = insertNodeNgramW
123 . map (\(NodeNgram n g p ngt lt w) ->
124 NodeNgram (pgNodeId n)
126 (pgNgramsParentId <$> p)
132 insertNodeNgramW :: [NodeNgramWrite] -> Cmd err Int
133 insertNodeNgramW nns =
134 mkCmd $ \c -> fromIntegral <$> runInsert_ c insertNothing
136 insertNothing = (Insert { iTable = nodeNgramTable
138 , iReturning = rCount
139 , iOnConflict = (Just DoNothing)
142 type NgramsText = Text
144 updateNodeNgrams' :: ListId -> [(NgramsTypeId, NgramsText, ListTypeId)] -> Cmd err ()
145 updateNodeNgrams' _ [] = pure ()
146 updateNodeNgrams' listId input = void $ execPGSQuery updateQuery (DPS.Only $ Values fields input')
148 fields = map (\t-> QualifiedIdentifier Nothing t) ["int4","int4","text","int4"]
149 input' = map (\(nt,t,lt) -> (listId, nt, t, lt)) input
151 updateNodeNgrams'_debug :: ListId -> [(NgramsTypeId, NgramsText, ListTypeId)] -> Cmd err ByteString
152 updateNodeNgrams'_debug listId input = formatPGSQuery updateQuery (DPS.Only $ Values fields input')
154 fields = map (\t-> QualifiedIdentifier Nothing t) ["int4","int4","text","int4"]
155 input' = map (\(nt,t,lt) -> (listId, nt, t, lt)) input
157 updateQuery :: DPS.Query
159 WITH new(node_id,ngrams_type,terms,typeList) as (?)
161 INSERT into nodes_ngrams (node_id,ngrams_id,ngrams_type,list_type,weight)
163 SELECT node_id,ngrams.id,ngrams_type,typeList,1 FROM new
164 JOIN ngrams ON ngrams.terms = new.terms
165 ON CONFLICT (node_id, ngrams_id, ngrams_type) DO
168 UPDATE SET list_type = excluded.list_type
172 data Action = Del | Add
173 type NgramsParent = Text
174 type NgramsChild = Text
176 ngramsGroup :: Action -> ListId -> [(NgramsTypeId, NgramsParent, NgramsChild)] -> Cmd err ()
177 ngramsGroup _ _ [] = pure ()
178 ngramsGroup a lid input = void $ trace (show input) $ execPGSQuery (ngramsGroupQuery a) (DPS.Only $ Values fields input')
180 fields = map (\t-> QualifiedIdentifier Nothing t) ["int4","int4","text","int4","text","text"]
181 input' = map (\(ntpid,p,c) -> (lid, nodeTypeId NodeList, userMaster, ntpid, p,c)) input
184 ngramsGroupQuery :: Action -> DPS.Query
185 ngramsGroupQuery a = case a of
187 WITH input(lid,listTypeId,masterUsername,ntype,parent_terms,child_terms)
189 -- (VALUES (15::"int4",5::"int4",'gargantua'::"text",4::"int4",'input'::"text",'designer'::"text"))),
192 SELECT n.id from nodes n
193 JOIN auth_user u ON n.user_id = u.id
194 JOIN input ON n.typename = input.listTypeId
195 WHERE u.username = input.masterUsername
200 -- FIRST import parent from master to user list
201 INSERT INTO nodes_ngrams (node_id,ngrams_id,parent_id,ngrams_type,list_type,weight)
202 SELECT input.lid,nn.ngrams_id,nn.parent_id,nn.ngrams_type,nn.list_type, nn.weight
204 JOIN ngrams ng ON ng.terms = input.parent_terms
205 JOIN nodes_ngrams nn ON nn.ngrams_id = ng.id
206 JOIN list_master ON nn.node_id = list_master.id
209 ON CONFLICT (node_id,ngrams_id,ngrams_type) DO NOTHING
212 INSERT INTO nodes_ngrams (node_id,ngrams_id,parent_id,ngrams_type,list_type,weight)
214 SELECT input.lid, nc.id, nnpu.id, input.ntype, nnmaster.list_type, nnmaster.weight
217 JOIN ngrams np ON np.terms = input.parent_terms
218 JOIN ngrams nc ON nc.terms = input.child_terms
220 JOIN nodes_ngrams nnpu ON nnpu.ngrams_id = np.id
221 JOIN nodes_ngrams nnmaster ON nnmaster.ngrams_id = nc.id
222 JOIN list_master ON nnmaster.node_id = list_master.id
225 nnpu.node_id = input.lid
226 AND nnpu.ngrams_type = input.ntype
228 AND nnmaster.ngrams_id = nc.id
229 AND nnmaster.ngrams_type = ntype
231 ON CONFLICT (node_id,ngrams_id,ngrams_type) DO
232 UPDATE SET parent_id = excluded.parent_id
237 WITH input(lid,listTypeId,masterUsername,ntype,parent_terms,child_terms)
239 -- (VALUES (15::"int4",5::"int4",'gargantua'::"text",4::"int4",'input'::"text",'designer'::"text"))),
242 SELECT n.id from nodes n
243 JOIN auth_user u ON n.user_id = u.id
244 JOIN input ON n.typename = input.listTypeId
245 WHERE u.username = input.masterUsername
250 -- FIRST import parent from master to user list
251 INSERT INTO nodes_ngrams (node_id,ngrams_id,parent_id,ngrams_type,list_type,weight)
252 SELECT input.lid,nn.ngrams_id,nn.parent_id,nn.ngrams_type,nn.list_type, nn.weight
254 JOIN ngrams ng ON ng.terms = input.parent_terms
255 JOIN nodes_ngrams nn ON nn.ngrams_id = ng.id
256 JOIN list_master ON nn.node_id = list_master.id
259 ON CONFLICT (node_id,ngrams_id,ngrams_type) DO NOTHING
262 INSERT INTO nodes_ngrams (node_id,ngrams_id,parent_id,ngrams_type,list_type,weight)
264 SELECT input.lid, nc.id, NULL, input.ntype, nnmaster.list_type, nnmaster.weight
267 JOIN ngrams np ON np.terms = input.parent_terms
268 JOIN ngrams nc ON nc.terms = input.child_terms
270 JOIN nodes_ngrams nnmaster ON nnmaster.ngrams_id = nc.id
271 JOIN list_master ON nnmaster.node_id = list_master.id
274 nnmaster.ngrams_id = nc.id
275 AND nnmaster.ngrams_type = ntype
277 ON CONFLICT (node_id,ngrams_id,ngrams_type) DO
278 UPDATE SET parent_id = NULL
283 data NodeNgramsUpdate = NodeNgramsUpdate
284 { _nnu_user_list_id :: ListId
285 , _nnu_lists_update :: [(NgramsTypeId, NgramsText, ListTypeId)]
286 , _nnu_add_children :: [(NgramsTypeId, NgramsParent, NgramsChild)]
287 , _nnu_rem_children :: [(NgramsTypeId, NgramsParent, NgramsChild)]
290 -- TODO wrap these updates in a transaction.
292 -- * check userId CanUpdateNgrams userListId
293 updateNodeNgrams :: NodeNgramsUpdate -> Cmd err ()
294 updateNodeNgrams nnu = do
295 updateNodeNgrams' userListId $ _nnu_lists_update nnu
296 ngramsGroup Del userListId $ _nnu_rem_children nnu
297 ngramsGroup Add userListId $ _nnu_add_children nnu
298 -- TODO remove duplicate line (fix SQL query)
299 ngramsGroup Add userListId $ _nnu_add_children nnu
301 userListId = _nnu_user_list_id nnu