2 Module : Gargantext.API.Ngrams.Tools
3 Description : Tools to manage Ngrams Elements (from the API)
4 Copyright : (c) CNRS, 2017-Present
5 License : AGPL + CECILL v3
6 Maintainer : team@gargantext.org
7 Stability : experimental
13 module Gargantext.API.Ngrams.Tools
16 import Control.Concurrent
17 import Control.Lens (_Just, (^.), at, view)
18 import Control.Monad.Reader
19 import Data.Map.Strict (Map)
21 import Data.Text (Text)
23 import Gargantext.API.Ngrams
24 import Gargantext.Core.Types (ListType(..), NodeId, ListId)
25 import Gargantext.Database.Schema.Ngrams (NgramsType)
26 import Gargantext.Prelude
27 import qualified Data.Map.Strict as Map
28 import qualified Data.Set as Set
32 getRepo :: RepoCmdM env err m => m NgramsRepo
37 listNgramsFromRepo :: [ListId] -> NgramsType
38 -> NgramsRepo -> Map Text NgramsRepoElement
39 listNgramsFromRepo nodeIds ngramsType repo = ngrams
41 ngramsMap = repo ^. r_state . at ngramsType . _Just
43 ngrams = Map.unionsWith mergeNgramsElement
44 [ ngramsMap ^. at nodeId . _Just | nodeId <- nodeIds ]
46 -- TODO-ACCESS: We want to do the security check before entering here.
47 -- Add a static capability parameter would be nice.
48 -- Ideally this is the access to `repoVar` which needs to
49 -- be properly guarded.
50 getListNgrams :: RepoCmdM env err m
51 => [ListId] -> NgramsType
52 -> m (Map Text NgramsRepoElement)
53 getListNgrams nodeIds ngramsType = listNgramsFromRepo nodeIds ngramsType <$> getRepo
55 getTermsWith :: (RepoCmdM env err m, Ord a)
56 => (Text -> a ) -> [ListId]
57 -> NgramsType -> ListType
59 getTermsWith f ls ngt lt = Map.fromListWith (<>)
60 <$> map (toTreeWith f)
62 <$> Map.filter (\f' -> (fst f') == lt)
63 <$> mapTermListRoot ls ngt
66 toTreeWith f'' (t, (_lt, maybeRoot)) = case maybeRoot of
67 Nothing -> (f'' t, [])
68 Just r -> (f'' r, map f'' [t])
70 mapTermListRoot :: [ListId] -> NgramsType
71 -> NgramsRepo -> Map Text (ListType, (Maybe Text))
72 mapTermListRoot nodeIds ngramsType repo =
73 Map.fromList [ (t, (_nre_list nre, _nre_root nre))
74 | (t, nre) <- Map.toList ngrams
76 where ngrams = listNgramsFromRepo nodeIds ngramsType repo
78 filterListWithRoot :: ListType -> Map Text (ListType, Maybe Text)
79 -> Map Text (Maybe RootTerm)
80 filterListWithRoot lt m = Map.fromList
81 $ map (\(t,(_,r)) -> (t,r))
82 $ filter isMapTerm (Map.toList m)
84 isMapTerm (_t,(l, maybeRoot)) = case maybeRoot of
86 Just r -> case Map.lookup r m of
87 Nothing -> panic $ "Garg.API.Ngrams.Tools: filterWithRoot, unknown key: " <> r
88 Just (l',_) -> l' == lt
90 groupNodesByNgrams :: Map Text (Maybe RootTerm)
91 -> Map Text (Set NodeId)
92 -> Map Text (Set NodeId)
93 groupNodesByNgrams syn occs = Map.fromListWith (<>) occs'
95 occs' = map toSyn (Map.toList occs)
96 toSyn (t,ns) = case Map.lookup t syn of
97 Nothing -> panic $ "[Garg.API.Ngrams.Tools.groupNodesByNgrams] unknown key: " <> t
102 data Diagonal = Diagonal Bool
104 getCoocByNgrams :: Diagonal -> Map Text (Set NodeId) -> Map (Text, Text) Int
105 getCoocByNgrams = getCoocByNgrams' identity
108 getCoocByNgrams' :: (Ord a, Ord c) => (b -> Set c) -> Diagonal -> Map a b -> Map (a, a) Int
109 getCoocByNgrams' f (Diagonal diag) m =
110 Map.fromList [( (t1,t2)
111 , maybe 0 Set.size $ Set.intersection
112 <$> (fmap f $ Map.lookup t1 m)
113 <*> (fmap f $ Map.lookup t2 m)
114 ) | (t1,t2) <- case diag of
115 True -> [ (x,y) | x <- Map.keys m, y <- Map.keys m, x <= y]
116 False -> listToCombi identity (Map.keys m)