]> Git — Sourcephile - gargantext.git/blob - src/Gargantext/Database/Action/Metrics.hs
[DB/FACTO] splitting Action into Action and Queries
[gargantext.git] / src / Gargantext / Database / Action / Metrics.hs
1 {-|
2 Module : Gargantext.Database.Metrics
3 Description : Get Metrics from Storage (Database like)
4 Copyright : (c) CNRS, 2017-Present
5 License : AGPL + CECILL v3
6 Maintainer : team@gargantext.org
7 Stability : experimental
8 Portability : POSIX
9
10 Node API
11 -}
12
13
14 {-# LANGUAGE OverloadedStrings #-}
15 {-# LANGUAGE NoImplicitPrelude #-}
16 {-# LANGUAGE FlexibleContexts #-}
17
18 module Gargantext.Database.Action.Metrics
19 where
20
21 import Data.Map (Map)
22 import Data.Text (Text)
23 import Gargantext.API.Ngrams (TabType(..), ngramsTypeFromTabType)
24 import Gargantext.API.Ngrams.Tools (filterListWithRoot, groupNodesByNgrams, Diagonal(..), getCoocByNgrams, mapTermListRoot, RootTerm, getRepo)
25 import Gargantext.Core.Types (ListType(..), Limit, NodeType(..))
26 import Gargantext.Database.Action.Flow (FlowCmdM)
27 import Gargantext.Database.Action.Metrics.NgramsByNode (getNodesByNgramsOnlyUser{-, getTficfWith-})
28 import Gargantext.Database.Admin.Config (userMaster)
29 import Gargantext.Database.Admin.Types.Node (ListId, CorpusId{-, HyperdataCorpus-})
30 import Gargantext.Database.Query.Table.Node (defaultList)
31 import Gargantext.Database.Query.Table.Node.Select
32 import Gargantext.Prelude
33 import Gargantext.Text.Metrics (scored, Scored(..), {-localMetrics, toScored-})
34 import qualified Data.Map as Map
35
36 getMetrics :: FlowCmdM env err m
37 => CorpusId -> Maybe ListId -> TabType -> Maybe Limit
38 -> m (Map Text (ListType, Maybe Text), [Scored Text])
39 getMetrics cId maybeListId tabType maybeLimit = do
40 (ngs, _, myCooc) <- getNgramsCooc cId maybeListId tabType maybeLimit
41 pure (ngs, scored myCooc)
42
43
44 getNgramsCooc :: (FlowCmdM env err m)
45 => CorpusId -> Maybe ListId -> TabType -> Maybe Limit
46 -> m ( Map Text (ListType, Maybe Text)
47 , Map Text (Maybe RootTerm)
48 , Map (Text, Text) Int
49 )
50 getNgramsCooc cId maybeListId tabType maybeLimit = do
51 (ngs', ngs) <- getNgrams cId maybeListId tabType
52
53 let
54 take' Nothing xs = xs
55 take' (Just n) xs = take n xs
56
57 lId <- defaultList cId
58 lIds <- selectNodesWithUsername NodeList userMaster
59
60 myCooc <- Map.filter (>1) <$> getCoocByNgrams (Diagonal True)
61 <$> groupNodesByNgrams ngs
62 <$> getNodesByNgramsOnlyUser cId (lIds <> [lId]) (ngramsTypeFromTabType tabType)
63 (take' maybeLimit $ Map.keys ngs)
64 pure $ (ngs', ngs, myCooc)
65
66
67
68 getNgrams :: (FlowCmdM env err m)
69 => CorpusId -> Maybe ListId -> TabType
70 -> m (Map Text (ListType, Maybe Text), Map Text (Maybe RootTerm))
71 getNgrams cId maybeListId tabType = do
72
73 lId <- case maybeListId of
74 Nothing -> defaultList cId
75 Just lId' -> pure lId'
76
77 lists <- mapTermListRoot [lId] (ngramsTypeFromTabType tabType) <$> getRepo
78 let maybeSyn = Map.unions $ map (\t -> filterListWithRoot t lists)
79 [GraphTerm, StopTerm, CandidateTerm]
80 pure (lists, maybeSyn)
81