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 MultiParamTypeClasses #-}
23 {-# LANGUAGE NoImplicitPrelude #-}
24 {-# LANGUAGE OverloadedStrings #-}
25 {-# LANGUAGE QuasiQuotes #-}
26 {-# LANGUAGE RankNTypes #-}
27 {-# LANGUAGE TemplateHaskell #-}
31 module Gargantext.Database.Schema.NodeNgram where
33 import Data.ByteString (ByteString)
34 import Data.Text (Text)
35 import Control.Lens.TH (makeLenses)
36 import Control.Monad (void)
37 import Data.Profunctor.Product.TH (makeAdaptorAndInstance)
38 import Database.PostgreSQL.Simple.Types (Values(..), QualifiedIdentifier(..))
39 import Database.PostgreSQL.Simple.SqlQQ (sql)
40 import Gargantext.Core.Types.Main (ListTypeId)
41 import Gargantext.Database.Utils (mkCmd, Cmd, execPGSQuery)
42 import Gargantext.Database.Types.Node (NodeId, ListId)
43 import Gargantext.Database.Schema.Node (pgNodeId)
44 import Gargantext.Database.Schema.Ngrams (NgramsTypeId, pgNgramsTypeId)
45 import Gargantext.Database.Schema.NodeNgramsNgrams (NgramsChild, NgramsParent, ngramsGroup, Action(..))
46 import Gargantext.Prelude
47 import Gargantext.Database.Utils (formatPGSQuery)
49 import qualified Database.PostgreSQL.Simple as PGS (Query)
52 data NodeNgramPoly node_id ngrams_id ngrams_type list_type weight
53 = NodeNgram { _nn_node_id :: node_id
54 , _nn_ngrams_id :: ngrams_id
55 , _nn_ngramsType :: ngrams_type
56 , _nn_listType :: list_type
57 , _nn_weight :: weight
76 type NodeNgramReadNull =
78 (Column (Nullable PGInt4 ))
79 (Column (Nullable PGInt4 ))
80 (Column (Nullable PGInt4 ))
81 (Column (Nullable PGInt4 ))
82 (Column (Nullable PGFloat8))
85 NodeNgramPoly NodeId Int NgramsTypeId Int Double
87 $(makeAdaptorAndInstance "pNodeNgram" ''NodeNgramPoly)
88 makeLenses ''NodeNgramPoly
90 nodeNgramTable :: Table NodeNgramWrite NodeNgramRead
91 nodeNgramTable = Table "nodes_ngrams"
92 ( pNodeNgram NodeNgram
93 { _nn_node_id = required "node_id"
94 , _nn_ngrams_id = required "ngrams_id"
95 , _nn_ngramsType = required "ngrams_type"
96 , _nn_listType = required "list_type"
97 , _nn_weight = required "weight"
101 queryNodeNgramTable :: Query NodeNgramRead
102 queryNodeNgramTable = queryTable nodeNgramTable
104 insertNodeNgrams :: [NodeNgram] -> Cmd err Int
105 insertNodeNgrams = insertNodeNgramW
106 . map (\(NodeNgram n g ngt lt w) ->
107 NodeNgram (pgNodeId n)
114 insertNodeNgramW :: [NodeNgramWrite] -> Cmd err Int
115 insertNodeNgramW nns =
116 mkCmd $ \c -> fromIntegral <$> runInsert_ c insertNothing
118 insertNothing = (Insert { iTable = nodeNgramTable
120 , iReturning = rCount
121 , iOnConflict = (Just DoNothing)
124 type NgramsText = Text
126 updateNodeNgrams' :: ListId -> [(NgramsTypeId, NgramsText, ListTypeId)] -> Cmd err ()
127 updateNodeNgrams' _ [] = pure ()
128 updateNodeNgrams' listId input = void $ execPGSQuery updateQuery (listId, Values fields input)
130 fields = map (\t-> QualifiedIdentifier Nothing t) ["int4","int4","text","int4"]
132 updateNodeNgrams'_debug :: ListId -> [(NgramsTypeId, NgramsText, ListTypeId)] -> Cmd err ByteString
133 updateNodeNgrams'_debug listId input = formatPGSQuery updateQuery (listId, Values fields input)
135 fields = map (\t-> QualifiedIdentifier Nothing t) ["int4","int4","text","int4"]
137 updateQuery :: PGS.Query
139 WITH new(node_id,ngrams_type,terms,typeList) as (?)
141 INSERT into nodes_ngrams (node_id,ngrams_id,ngrams_type,list_type,weight)
143 SELECT node_id,ngrams.id,ngrams_type,typeList,1 FROM new
144 JOIN ngrams ON ngrams.terms = new.terms
145 ON CONFLICT (node_id, ngrams_id, ngrams_type) DO
148 UPDATE SET list_type = excluded.list_type
155 data NodeNgramsUpdate = NodeNgramsUpdate
156 { _nnu_user_list_id :: ListId
157 , _nnu_lists_update :: [(NgramsTypeId, NgramsText, ListTypeId)]
158 , _nnu_add_children :: [(NgramsParent, NgramsChild, Maybe Double)]
159 , _nnu_rem_children :: [(NgramsParent, NgramsChild, Maybe Double)]
162 -- TODO wrap these updates in a transaction.
163 updateNodeNgrams :: NodeNgramsUpdate -> Cmd err ()
164 updateNodeNgrams nnu = do
165 updateNodeNgrams' userListId $ _nnu_lists_update nnu
166 ngramsGroup Del userListId $ _nnu_rem_children nnu
167 ngramsGroup Add userListId $ _nnu_add_children nnu
169 userListId = _nnu_user_list_id nnu