2 Module : Gargantext.API.Metrics
3 Description : Server API
4 Copyright : (c) CNRS, 2017-Present
5 License : AGPL + CECILL v3
6 Maintainer : team@gargantext.org
7 Stability : experimental
14 {-# OPTIONS_GHC -fno-warn-orphans #-}
16 {-# LANGUAGE TypeOperators #-}
18 module Gargantext.API.Metrics
22 import Data.Text (Text)
23 import Data.Time (UTCTime)
24 import Data.Vector (Vector)
25 import Gargantext.API.HashedResponse
26 import Gargantext.API.Ngrams.NgramsTree
27 import Gargantext.API.Ngrams.Types
28 import Gargantext.API.Prelude (GargServer)
29 import Gargantext.Core.Text.Metrics (Scored(..), {-normalizeGlobal,-} normalizeLocal)
30 import Gargantext.Core.Types (CorpusId, Limit, ListId, ListType(..))
31 import Gargantext.Core.Viz.Chart
32 import Gargantext.Core.Viz.Types
33 import Gargantext.Database.Admin.Types.Hyperdata (HyperdataList(..), hl_chart, hl_pie, hl_scatter, hl_tree)
34 import Gargantext.Database.Admin.Types.Metrics (ChartMetrics(..), Metric(..), Metrics(..))
35 import Gargantext.Database.Admin.Types.Node (NodeId)
36 import Gargantext.Database.Action.Flow.Types (FlowCmdM)
37 import Gargantext.Database.Prelude
38 import Gargantext.Database.Query.Table.Node (defaultList, getNodeWith)
39 import Gargantext.Database.Query.Table.Node.Error (HasNodeError)
40 import Gargantext.Database.Query.Table.Node.UpdateOpaleye (updateHyperdata)
41 import Gargantext.Database.Schema.Node (node_hyperdata)
42 import Gargantext.Prelude
44 import qualified Data.HashMap.Strict as HashMap
45 import qualified Gargantext.Database.Action.Metrics as Metrics
47 -------------------------------------------------------------
48 -- | Scatter metrics API
49 type ScatterAPI = Summary "SepGen IncExc metrics"
50 :> QueryParam "list" ListId
51 :> QueryParamR "ngramsType" TabType
52 :> QueryParam "limit" Int
53 :> Get '[JSON] (HashedResponse Metrics)
54 :<|> Summary "Scatter update"
55 :> QueryParam "list" ListId
56 :> QueryParamR "ngramsType" TabType
57 :> QueryParam "limit" Int
59 :<|> "hash" :> Summary "Scatter Hash"
60 :> QueryParam "list" ListId
61 :> QueryParamR "ngramsType" TabType
64 scatterApi :: NodeId -> GargServer ScatterAPI
65 scatterApi id' = getScatter id'
66 :<|> updateScatter id'
67 :<|> getScatterHash id'
69 getScatter :: FlowCmdM env err m =>
74 -> m (HashedResponse Metrics)
75 getScatter cId maybeListId tabType _maybeLimit = do
76 listId <- case maybeListId of
78 Nothing -> defaultList cId
79 node <- getNodeWith listId (Proxy :: Proxy HyperdataList)
80 let HyperdataList { _hl_scatter = scatterMap } = node ^. node_hyperdata
81 mChart = HashMap.lookup tabType scatterMap
83 chart <- case mChart of
84 Just chart -> pure chart
86 updateScatter' cId maybeListId tabType Nothing
88 pure $ constructHashedResponse chart
90 updateScatter :: FlowCmdM env err m =>
96 updateScatter cId maybeListId tabType maybeLimit = do
97 printDebug "[updateScatter] cId" cId
98 printDebug "[updateScatter] maybeListId" maybeListId
99 printDebug "[updateScatter] tabType" tabType
100 printDebug "[updateScatter] maybeLimit" maybeLimit
101 _ <- updateScatter' cId maybeListId tabType maybeLimit
104 updateScatter' :: FlowCmdM env err m =>
110 updateScatter' cId maybeListId tabType maybeLimit = do
111 (ngs', scores) <- Metrics.getMetrics cId maybeListId tabType maybeLimit
114 metrics = fmap (\(Scored t s1 s2) -> Metric { m_label = unNgramsTerm t
117 , m_cat = listType t ngs' })
118 $ fmap normalizeLocal scores
119 listType t m = maybe (panic errorMsg) fst $ HashMap.lookup t m
120 errorMsg = "API.Node.metrics: key absent"
122 listId <- case maybeListId of
124 Nothing -> defaultList cId
125 node <- getNodeWith listId (Proxy :: Proxy HyperdataList)
126 let hl = node ^. node_hyperdata
127 scatterMap = hl ^. hl_scatter
128 _ <- updateHyperdata listId $ hl { _hl_scatter = HashMap.insert tabType (Metrics metrics) scatterMap }
130 pure $ Metrics metrics
132 getScatterHash :: FlowCmdM env err m =>
137 getScatterHash cId maybeListId tabType = do
138 hash <$> getScatter cId maybeListId tabType Nothing
141 -------------------------------------------------------------
142 -- | Chart metrics API
143 type ChartApi = Summary " Chart API"
144 :> QueryParam "from" UTCTime
145 :> QueryParam "to" UTCTime
146 :> QueryParam "list" ListId
147 :> QueryParamR "ngramsType" TabType
148 :> Get '[JSON] (HashedResponse (ChartMetrics Histo))
149 :<|> Summary "Chart update"
150 :> QueryParam "list" ListId
151 :> QueryParamR "ngramsType" TabType
152 :> QueryParam "limit" Int
154 :<|> "hash" :> Summary "Chart Hash"
155 :> QueryParam "list" ListId
156 :> QueryParamR "ngramsType" TabType
159 chartApi :: NodeId -> GargServer ChartApi
160 chartApi id' = getChart id'
162 :<|> getChartHash id'
164 -- TODO add start / end
165 getChart :: FlowCmdM env err m =>
171 -> m (HashedResponse (ChartMetrics Histo))
172 getChart cId _start _end maybeListId tabType = do
173 listId <- case maybeListId of
175 Nothing -> defaultList cId
176 node <- getNodeWith listId (Proxy :: Proxy HyperdataList)
177 let chartMap = node ^. node_hyperdata ^. hl_chart
178 mChart = HashMap.lookup tabType chartMap
180 chart <- case mChart of
181 Just chart -> pure chart
183 updateChart' cId maybeListId tabType Nothing
185 pure $ constructHashedResponse chart
187 updateChart :: HasNodeError err =>
193 updateChart cId maybeListId tabType maybeLimit = do
194 printDebug "[updateChart] cId" cId
195 printDebug "[updateChart] maybeListId" maybeListId
196 printDebug "[updateChart] tabType" tabType
197 printDebug "[updateChart] maybeLimit" maybeLimit
198 _ <- updateChart' cId maybeListId tabType maybeLimit
201 updateChart' :: HasNodeError err =>
206 -> Cmd err (ChartMetrics Histo)
207 updateChart' cId maybeListId tabType _maybeLimit = do
208 listId <- case maybeListId of
210 Nothing -> defaultList cId
211 node <- getNodeWith listId (Proxy :: Proxy HyperdataList)
212 let hl = node ^. node_hyperdata
213 chartMap = hl ^. hl_chart
215 _ <- updateHyperdata listId $ hl { _hl_chart = HashMap.insert tabType (ChartMetrics h) chartMap }
217 pure $ ChartMetrics h
220 getChartHash :: FlowCmdM env err m =>
225 getChartHash cId maybeListId tabType = do
226 hash <$> getChart cId Nothing Nothing maybeListId tabType
228 -------------------------------------------------------------
230 type PieApi = Summary "Pie Chart"
231 :> QueryParam "from" UTCTime
232 :> QueryParam "to" UTCTime
233 :> QueryParam "list" ListId
234 :> QueryParamR "ngramsType" TabType
235 :> Get '[JSON] (HashedResponse (ChartMetrics Histo))
236 :<|> Summary "Pie Chart update"
237 :> QueryParam "list" ListId
238 :> QueryParamR "ngramsType" TabType
239 :> QueryParam "limit" Int
241 :<|> "hash" :> Summary "Pie Hash"
242 :> QueryParam "list" ListId
243 :> QueryParamR "ngramsType" TabType
246 pieApi :: NodeId -> GargServer PieApi
247 pieApi id' = getPie id'
251 getPie :: FlowCmdM env err m
257 -> m (HashedResponse (ChartMetrics Histo))
258 getPie cId _start _end maybeListId tabType = do
259 listId <- case maybeListId of
261 Nothing -> defaultList cId
262 node <- getNodeWith listId (Proxy :: Proxy HyperdataList)
263 let pieMap = node ^. node_hyperdata ^. hl_pie
264 mChart = HashMap.lookup tabType pieMap
266 chart <- case mChart of
267 Just chart -> pure chart
269 updatePie' cId maybeListId tabType Nothing
271 pure $ constructHashedResponse chart
273 updatePie :: FlowCmdM env err m =>
279 updatePie cId maybeListId tabType maybeLimit = do
280 printDebug "[updatePie] cId" cId
281 printDebug "[updatePie] maybeListId" maybeListId
282 printDebug "[updatePie] tabType" tabType
283 printDebug "[updatePie] maybeLimit" maybeLimit
284 _ <- updatePie' cId maybeListId tabType maybeLimit
287 updatePie' :: FlowCmdM env err m =>
292 -> m (ChartMetrics Histo)
293 updatePie' cId maybeListId tabType _maybeLimit = do
294 listId <- case maybeListId of
296 Nothing -> defaultList cId
297 node <- getNodeWith listId (Proxy :: Proxy HyperdataList)
298 let hl = node ^. node_hyperdata
299 pieMap = hl ^. hl_pie
301 p <- chartData cId (ngramsTypeFromTabType tabType) MapTerm
302 _ <- updateHyperdata listId $ hl { _hl_pie = HashMap.insert tabType (ChartMetrics p) pieMap }
304 pure $ ChartMetrics p
306 getPieHash :: FlowCmdM env err m =>
311 getPieHash cId maybeListId tabType = do
312 hash <$> getPie cId Nothing Nothing maybeListId tabType
314 -------------------------------------------------------------
315 -- | Tree metrics API
317 type TreeApi = Summary " Tree API"
318 :> QueryParam "from" UTCTime
319 :> QueryParam "to" UTCTime
320 :> QueryParam "list" ListId
321 :> QueryParamR "ngramsType" TabType
322 :> QueryParamR "listType" ListType
323 :> Get '[JSON] (HashedResponse (ChartMetrics (Vector NgramsTree)))
324 :<|> Summary "Tree Chart update"
325 :> QueryParam "list" ListId
326 :> QueryParamR "ngramsType" TabType
327 :> QueryParamR "listType" ListType
331 :> QueryParam "list" ListId
332 :> QueryParamR "ngramsType" TabType
333 :> QueryParamR "listType" ListType
335 treeApi :: NodeId -> GargServer TreeApi
336 treeApi id' = getTree id'
340 getTree :: FlowCmdM env err m
347 -> m (HashedResponse (ChartMetrics (Vector NgramsTree)))
348 getTree cId _start _end maybeListId tabType listType = do
349 listId <- case maybeListId of
351 Nothing -> defaultList cId
353 node <- getNodeWith listId (Proxy :: Proxy HyperdataList)
354 let treeMap = node ^. node_hyperdata ^. hl_tree
355 mChart = HashMap.lookup tabType treeMap
357 chart <- case mChart of
358 Just chart -> pure chart
360 updateTree' cId maybeListId tabType listType
362 pure $ constructHashedResponse chart
364 updateTree :: FlowCmdM env err m =>
370 updateTree cId maybeListId tabType listType = do
371 printDebug "[updateTree] cId" cId
372 printDebug "[updateTree] maybeListId" maybeListId
373 printDebug "[updateTree] tabType" tabType
374 printDebug "[updateTree] listType" listType
375 _ <- updateTree' cId maybeListId tabType listType
378 updateTree' :: FlowCmdM env err m =>
383 -> m (ChartMetrics (Vector NgramsTree))
384 updateTree' cId maybeListId tabType listType = do
385 listId <- case maybeListId of
387 Nothing -> defaultList cId
389 node <- getNodeWith listId (Proxy :: Proxy HyperdataList)
390 let hl = node ^. node_hyperdata
391 treeMap = hl ^. hl_tree
392 t <- treeData cId (ngramsTypeFromTabType tabType) listType
393 _ <- updateHyperdata listId $ hl { _hl_tree = HashMap.insert tabType (ChartMetrics t) treeMap }
395 pure $ ChartMetrics t
397 getTreeHash :: FlowCmdM env err m =>
403 getTreeHash cId maybeListId tabType listType = do
404 hash <$> getTree cId Nothing Nothing maybeListId tabType listType