2 Module : Gargantext.Database.Query.Table.Ngrams
3 Description : Deal with in Gargantext Database.
4 Copyright : (c) CNRS, 2017-Present
5 License : AGPL + CECILL v3
6 Maintainer : team@gargantext.org
7 Stability : experimental
12 {-# LANGUAGE Arrows #-}
13 {-# LANGUAGE QuasiQuotes #-}
14 {-# LANGUAGE TemplateHaskell #-}
16 module Gargantext.Database.Query.Table.Ngrams
17 ( module Gargantext.Database.Schema.Ngrams
24 import Control.Lens ((^.))
25 import Data.ByteString.Internal (ByteString)
26 import Data.Map (Map, fromList)
27 import Data.Text (Text)
28 import qualified Database.PostgreSQL.Simple as PGS
30 import Gargantext.Core.Types
31 import Gargantext.Database.Prelude (runOpaQuery, Cmd)
32 import Gargantext.Database.Prelude (runPGSQuery, formatPGSQuery)
33 import Gargantext.Database.Query.Table.NodeNodeNgrams
34 import Gargantext.Database.Schema.Ngrams
35 import Gargantext.Database.Schema.Prelude
36 import Gargantext.Database.Types
37 import Gargantext.Prelude
39 queryNgramsTable :: Query NgramsRead
40 queryNgramsTable = queryTable ngramsTable
42 selectNgramsByDoc :: [ListId] -> DocId -> NgramsType -> Cmd err [Text]
43 selectNgramsByDoc lIds dId nt = runOpaQuery (query lIds dId nt)
46 join :: Query (NgramsRead, NodeNodeNgramsReadNull)
47 join = leftJoin queryNgramsTable queryNodeNodeNgramsTable on1
49 on1 (ng,nnng) = ng^.ngrams_id .== nnng^.nnng_ngrams_id
51 query cIds' dId' nt' = proc () -> do
52 (ng,nnng) <- join -< ()
53 restrict -< foldl (\b cId -> ((toNullable $ pgNodeId cId) .== nnng^.nnng_node1_id) .|| b) (pgBool True) cIds'
54 restrict -< (toNullable $ pgNodeId dId') .== nnng^.nnng_node2_id
55 restrict -< (toNullable $ pgNgramsType nt') .== nnng^.nnng_ngramsType
56 returnA -< ng^.ngrams_terms
59 _postNgrams :: CorpusId -> DocId -> [Text] -> Cmd err Int
60 _postNgrams = undefined
62 _dbGetNgramsDb :: Cmd err [NgramsDB]
63 _dbGetNgramsDb = runOpaQuery queryNgramsTable
66 -- TODO-ACCESS: access must not be checked here but when insertNgrams is called.
67 insertNgrams :: [Ngrams] -> Cmd err (Map Text NgramsId)
68 insertNgrams ns = fromList <$> map (\(Indexed i t) -> (t, i)) <$> (insertNgrams' ns)
70 -- TODO-ACCESS: access must not be checked here but when insertNgrams' is called.
71 insertNgrams' :: [Ngrams] -> Cmd err [Indexed Int Text]
72 insertNgrams' ns = runPGSQuery queryInsertNgrams (PGS.Only $ Values fields ns)
74 fields = map (\t -> QualifiedIdentifier Nothing t) ["text", "int4"]
76 _insertNgrams_Debug :: [(Text, Size)] -> Cmd err ByteString
77 _insertNgrams_Debug ns = formatPGSQuery queryInsertNgrams (PGS.Only $ Values fields ns)
79 fields = map (\t -> QualifiedIdentifier Nothing t) ["text", "int4"]
81 ----------------------
82 queryInsertNgrams :: PGS.Query
83 queryInsertNgrams = [sql|
84 WITH input_rows(terms,n) AS (?)
86 INSERT INTO ngrams (terms,n)
87 SELECT * FROM input_rows
88 ON CONFLICT (terms) DO NOTHING -- unique index created here
97 JOIN ngrams c USING (terms); -- columns of unique index