]> Git — Sourcephile - gargantext.git/blob - src/Gargantext/Database/Metrics/Count.hs
[Files] Missing.
[gargantext.git] / src / Gargantext / Database / Metrics / Count.hs
1 {-|
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
8 Portability : POSIX
9
10 Count Ngrams by Context
11
12 -}
13
14 {-# LANGUAGE NoImplicitPrelude #-}
15 {-# LANGUAGE OverloadedStrings #-}
16 {-# LANGUAGE QuasiQuotes #-}
17
18 module Gargantext.Database.Metrics.Count where
19
20 import Control.Lens (view)
21 import Data.Map.Strict (Map, fromListWith, elems)
22 import Data.Text (Text)
23 import Database.PostgreSQL.Simple.SqlQQ (sql)
24 import Gargantext.Database.Schema.Node (HasNodeError(..))
25 import Gargantext.Prelude
26 import Gargantext.Core.Types.Main (listTypeId, ListType(..))
27 import Gargantext.Text.Metrics.Count (Coocs, coocOn)
28 import Gargantext.Database.Utils (Cmd, runPGSQuery)
29 import Gargantext.Database.Types.Node (ListId, CorpusId)
30 import Gargantext.Database.Types.Node (NodeId)
31 import Gargantext.Database.Schema.Ngrams (NgramsId, NgramsType(..), ngramsTypeId, Ngrams(..), NgramsIndexed(..), ngrams, ngramsTerms)
32
33 getCoocByDocDev :: HasNodeError err => CorpusId -> ListId -> Cmd err (Map ([Text], [Text]) Coocs)
34 getCoocByDocDev cId lId = coocOn (\n-> [ view ( ngrams . ngramsTerms) n]) <$> getNgramsByDoc cId lId
35
36 getCoocByDoc :: CorpusId -> ListId -> Cmd err (Map (NgramsIndexed, NgramsIndexed) Coocs)
37 getCoocByDoc cId lId = coocOn identity <$> getNgramsByDoc cId lId
38
39
40 getNgramsByDoc :: CorpusId -> ListId -> Cmd err [[NgramsIndexed]]
41 getNgramsByDoc cId lId =
42 elems
43 <$> fromListWith (<>)
44 <$> map (\(nId, ngId, nt, n) -> (nId, [NgramsIndexed (Ngrams nt n) ngId]))
45 <$> getNgramsByDocDb cId lId
46
47
48 getNgramsByDocDb :: CorpusId -> ListId -> Cmd err [(NodeId, NgramsId, Text, Int)]
49 getNgramsByDocDb cId lId = runPGSQuery query params
50 where
51 params = (cId, lId, listTypeId GraphList, ngramsTypeId NgramsTerms)
52 query = [sql|
53
54 -- TODO add CTE
55 SELECT n.id, ng.id, ng.terms, ng.n -- , list.parent_id
56 FROM nodes n
57 JOIN nodes_nodes nn ON nn.node2_id = n.id
58 JOIN nodes_ngrams nng ON nng.node_id = nn.node2_id
59 JOIN nodes_ngrams list ON list.ngrams_id = nng.ngrams_id
60 JOIN ngrams ng ON ng.id = nng.ngrams_id
61 WHERE nn.node1_id = ? -- CorpusId
62 AND list.node_id = ? -- ListId
63 AND list.list_type = ? -- GraphListId
64 AND list.ngrams_type = ? -- NgramsTypeId
65
66 |]