]> Git — Sourcephile - gargantext.git/blob - src/Gargantext/API/Ngrams/Tools.hs
[PHYLO) Backend + flowPhylo + SVG.
[gargantext.git] / src / Gargantext / API / Ngrams / Tools.hs
1 {-|
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
8 Portability : POSIX
9
10 -}
11
12 {-# LANGUAGE NoImplicitPrelude #-}
13 {-# LANGUAGE OverloadedStrings #-}
14 {-# LANGUAGE RankNTypes #-}
15
16 module Gargantext.API.Ngrams.Tools
17 where
18
19 import Control.Concurrent
20 import Control.Lens (_Just, (^.), at, view)
21 import Control.Monad.Reader
22 import Data.Map.Strict (Map)
23 import Data.Set (Set)
24 import Data.Text (Text)
25 import Data.Validity
26 import Gargantext.API.Ngrams
27 import Gargantext.Core.Types (ListType(..), NodeId, ListId)
28 import Gargantext.Database.Schema.Ngrams (NgramsType)
29 import Gargantext.Prelude
30 import qualified Data.Map.Strict as Map
31 import qualified Data.Set as Set
32
33
34 type RootTerm = Text
35
36
37 getListNgrams :: RepoCmdM env err m
38 => [ListId] -> NgramsType
39 -> m (Map Text NgramsRepoElement)
40 getListNgrams nodeIds ngramsType = do
41 v <- view repoVar
42 repo <- liftIO $ readMVar v
43
44 let
45 ngramsMap = repo ^. r_state . at ngramsType . _Just
46
47 ngrams = Map.unionsWith mergeNgramsElement
48 [ ngramsMap ^. at nodeId . _Just | nodeId <- nodeIds ]
49
50 pure ngrams
51
52 getTermsWith :: (RepoCmdM env err m, Ord a)
53 => (Text -> a ) -> [ListId]
54 -> NgramsType -> ListType
55 -> m (Map a [a])
56 getTermsWith f ls ngt lt = Map.fromListWith (<>)
57 <$> map (toTreeWith f)
58 <$> Map.toList
59 <$> Map.filter (\f' -> (fst f') == lt)
60 <$> mapTermListRoot ls ngt
61 where
62 toTreeWith f'' (t, (_lt, maybeRoot)) = case maybeRoot of
63 Nothing -> (f'' t, [])
64 Just r -> (f'' r, map f'' [t])
65
66 mapTermListRoot :: RepoCmdM env err m
67 => [ListId] -> NgramsType
68 -> m (Map Text (ListType, (Maybe Text)))
69 mapTermListRoot nodeIds ngramsType = do
70 ngrams <- getListNgrams nodeIds ngramsType
71 pure $ Map.fromList [(t, (_nre_list nre, _nre_root nre))
72 | (t, nre) <- Map.toList ngrams
73 ]
74
75 filterListWithRoot :: ListType -> Map Text (ListType, Maybe Text)
76 -> Map Text (Maybe RootTerm)
77 filterListWithRoot lt m = Map.fromList
78 $ map (\(t,(_,r)) -> (t,r))
79 $ filter isGraphTerm (Map.toList m)
80 where
81 isGraphTerm (_t,(l, maybeRoot)) = case maybeRoot of
82 Nothing -> l == lt
83 Just r -> case Map.lookup r m of
84 Nothing -> panic $ "Garg.API.Ngrams.Tools: filterWithRoot, unknown key: " <> r
85 Just (l',_) -> l' == lt
86
87 groupNodesByNgrams :: Map Text (Maybe RootTerm)
88 -> Map Text (Set NodeId)
89 -> Map Text (Set NodeId)
90 groupNodesByNgrams syn occs = Map.fromListWith (<>) occs'
91 where
92 occs' = map toSyn (Map.toList occs)
93 toSyn (t,ns) = case Map.lookup t syn of
94 Nothing -> panic $ "[Garg.API.Ngrams.Tools.groupNodesByNgrams] unknown key: " <> t
95 Just r -> case r of
96 Nothing -> (t, ns)
97 Just r' -> (r',ns)
98
99 data Diagonal = Diagonal Bool
100
101 getCoocByNgrams :: Diagonal -> Map Text (Set NodeId) -> Map (Text, Text) Int
102 getCoocByNgrams = getCoocByNgrams' identity
103
104
105 getCoocByNgrams' :: (Ord a, Ord c) => (b -> Set c) -> Diagonal -> Map a b -> Map (a, a) Int
106 getCoocByNgrams' f (Diagonal diag) m =
107 Map.fromList [((t1,t2)
108 ,maybe 0 Set.size $ Set.intersection
109 <$> (fmap f $ Map.lookup t1 m)
110 <*> (fmap f $ Map.lookup t2 m)
111 ) | (t1,t2) <- case diag of
112 True -> [ (x,y) | x <- Map.keys m, y <- Map.keys m, x <= y]
113 False -> listToCombi identity (Map.keys m)
114 ]
115
116
117