]> Git — Sourcephile - gargantext.git/blob - src/Gargantext/Database/Action/Metrics/TFICF.hs
Merge branch '97-dev-istex-search' of ssh://gitlab.iscpif.fr:20022/gargantext/haskell...
[gargantext.git] / src / Gargantext / Database / Action / Metrics / TFICF.hs
1 {-|
2 Module : Gargantext.Database.Metrics.TFICF
3 Description : Ngrams by Node user and master
4 Copyright : (c) CNRS, 2017-Present
5 License : AGPL + CECILL v3
6 Maintainer : team@gargantext.org
7 Stability : experimental
8 Portability : POSIX
9
10 -}
11
12 {-# LANGUAGE QuasiQuotes #-}
13
14 module Gargantext.Database.Action.Metrics.TFICF
15 where
16
17 -- import Debug.Trace (trace)
18 -- import Gargantext.Core (Lang(..))
19 import Data.HashMap.Strict (HashMap)
20 import qualified Data.HashMap.Strict as HM
21 import Data.Maybe (fromMaybe)
22 import Gargantext.Core
23 import Gargantext.Core.Text.Metrics.TFICF
24 import Gargantext.Database.Action.Metrics.NgramsByContext (getContextsByNgramsUser, {-getOccByNgramsOnlyFast,-} getOccByNgramsOnlyFast_withSample)
25 import Gargantext.Database.Admin.Types.Node -- (ListId, CorpusId, NodeId)
26 import Gargantext.Database.Prelude (Cmd)
27 import Gargantext.Database.Query.Table.NodeContext (selectCountDocs)
28 import Gargantext.Database.Schema.Ngrams (NgramsType(..))
29 import Gargantext.API.Ngrams.Types
30 import Gargantext.Prelude
31 import qualified Data.Set as Set
32
33 {-
34 getTficf :: HasDBid NodeType
35 => UserCorpusId
36 -> MasterCorpusId
37 -> NgramsType
38 -> Cmd err (HashMap NgramsTerm Double)
39 getTficf cId mId nt = do
40 mapTextDoubleLocal <- HM.filter (> 1)
41 <$> HM.map (fromIntegral . Set.size)
42 <$> getContextsByNgramsUser cId nt
43
44 mapTextDoubleGlobal <- HM.map fromIntegral
45 <$> getOccByNgramsOnlyFast mId nt (HM.keys mapTextDoubleLocal)
46
47 countLocal <- selectCountDocs cId
48 countGlobal <- selectCountDocs mId
49
50 printDebug "getTficf" (mapTextDoubleLocal, mapTextDoubleGlobal, countLocal, countGlobal)
51
52 pure $ HM.mapWithKey (\t n ->
53 tficf (TficfInfra (Count n )
54 (Total $ fromIntegral countLocal))
55 (TficfSupra (Count $ fromMaybe 0 $ HM.lookup t mapTextDoubleGlobal)
56 (Total $ fromIntegral countGlobal))
57 ) mapTextDoubleLocal
58 -}
59
60 getTficf_withSample :: HasDBid NodeType
61 => UserCorpusId
62 -> MasterCorpusId
63 -> NgramsType
64 -> Cmd err (HashMap NgramsTerm Double)
65 getTficf_withSample cId mId nt = do
66 mapTextDoubleLocal <- HM.filter (> 1)
67 <$> HM.map (fromIntegral . Set.size)
68 <$> getContextsByNgramsUser cId nt
69
70 countLocal <- selectCountDocs cId
71 let countGlobal = countLocal * 10
72
73 mapTextDoubleGlobal <- HM.map fromIntegral
74 <$> getOccByNgramsOnlyFast_withSample mId countGlobal nt
75 (HM.keys mapTextDoubleLocal)
76
77 --printDebug "getTficf_withSample" (mapTextDoubleLocal, mapTextDoubleGlobal, countLocal, countGlobal)
78 pure $ HM.mapWithKey (\t n ->
79 tficf (TficfInfra (Count n )
80 (Total $ fromIntegral countLocal))
81 (TficfSupra (Count $ fromMaybe 0 $ HM.lookup t mapTextDoubleGlobal)
82 (Total $ fromIntegral countGlobal))
83 ) mapTextDoubleLocal
84