2 Module : Gargantext.Database.Metrics.Count
3 Description : Ngram connection to the Database
4 Copyright : (c) CNRS, 2017-Present
5 License : AGPL + CECILL v3
6 Maintainer : team@gargantext.org
7 Stability : experimental
10 Count Ngrams by Context
14 {-# LANGUAGE NoImplicitPrelude #-}
15 {-# LANGUAGE OverloadedStrings #-}
16 {-# LANGUAGE QuasiQuotes #-}
17 {-# LANGUAGE RankNTypes #-}
19 module Gargantext.Database.Metrics.Count where
21 import Control.Lens (view)
22 import Data.Map.Strict (Map, fromListWith, elems)
23 import Data.Text (Text)
24 import Database.PostgreSQL.Simple.SqlQQ (sql)
25 import Gargantext.Database.Schema.Node (HasNodeError(..))
26 import Gargantext.Prelude
27 import Gargantext.Core.Types.Main (listTypeId, ListType(..))
28 import Gargantext.Text.Metrics.Count (Coocs, coocOn)
29 import Gargantext.Database.Utils (Cmd, runPGSQuery)
30 import Gargantext.Database.Types.Node (ListId, CorpusId)
31 import Gargantext.Database.Types.Node (NodeId)
32 import Gargantext.Database.Schema.Ngrams (NgramsId, NgramsType(..), ngramsTypeId, Ngrams(..), NgramsIndexed(..), ngrams, ngramsTerms)
34 getCoocByDocDev :: HasNodeError err => CorpusId -> ListId -> Cmd err (Map ([Text], [Text]) Int)
35 getCoocByDocDev cId lId = coocOn (\n-> [ view ( ngrams . ngramsTerms) n]) <$> getNgramsByDoc cId lId
37 getCoocByDoc :: CorpusId -> ListId -> Cmd err (Map (NgramsIndexed, NgramsIndexed) Coocs)
38 getCoocByDoc cId lId = coocOn identity <$> getNgramsByDoc cId lId
41 getNgramsByDoc :: CorpusId -> ListId -> Cmd err [[NgramsIndexed]]
42 getNgramsByDoc cId lId =
45 <$> map (\(nId, ngId, nt, n) -> (nId, [NgramsIndexed (Ngrams nt n) ngId]))
46 <$> getNgramsByDocDb cId lId
49 getNgramsByDocDb :: CorpusId -> ListId -> Cmd err [(NodeId, NgramsId, Text, Int)]
50 getNgramsByDocDb cId lId = runPGSQuery query params
52 params = (cId, lId, listTypeId GraphList, ngramsTypeId NgramsTerms)
56 SELECT n.id, ng.id, ng.terms, ng.n -- , list.parent_id
58 JOIN nodes_nodes nn ON nn.node2_id = n.id
59 JOIN nodes_ngrams nng ON nng.node_id = nn.node2_id
60 JOIN nodes_ngrams list ON list.ngrams_id = nng.ngrams_id
61 JOIN ngrams ng ON ng.id = nng.ngrams_id
62 WHERE nn.node1_id = ? -- CorpusId
63 AND list.node_id = ? -- ListId
64 AND list.list_type = ? -- GraphListId
65 AND list.ngrams_type = ? -- NgramsTypeId