[REFACT] FlowList integration to Terms with instances
[gargantext.git] / src / Gargantext / API / Metrics.hs
index ea192a95620ea2a6cc4bb5759b88b69695ed8b81..015d7d25e97a1ae0f88139be6a5fc6290e714ef9 100644 (file)
@@ -13,32 +13,36 @@ Metrics API
 
 {-# OPTIONS_GHC -fno-warn-orphans #-}
 
-{-# LANGUAGE TemplateHaskell    #-}
 {-# LANGUAGE TypeOperators      #-}
 
 module Gargantext.API.Metrics
     where
 
 import Control.Lens
+import qualified Data.Map as Map
+import Data.Text (Text)
 import Data.Time (UTCTime)
 import Servant
-import qualified Data.Map as Map
 
-import Gargantext.API.Ngrams
+import Gargantext.API.HashedResponse
 import Gargantext.API.Ngrams.NTree
+import Gargantext.API.Ngrams.Types
+import Gargantext.API.Prelude (GargServer)
 import Gargantext.Core.Types (CorpusId, Limit, ListId, ListType(..))
-import qualified Gargantext.Database.Action.Metrics as Metrics
 import Gargantext.Database.Action.Flow
-import Gargantext.Database.Admin.Types.Hyperdata (HyperdataList(..))
+import Gargantext.Database.Admin.Types.Hyperdata (HyperdataList(..), hl_chart, hl_pie, hl_scatter, hl_tree)
 import Gargantext.Database.Admin.Types.Metrics (ChartMetrics(..), Metric(..), Metrics(..))
+import Gargantext.Database.Admin.Types.Node (NodeId)
+import Gargantext.Database.Prelude
 import Gargantext.Database.Query.Table.Node (defaultList, getNodeWith)
+import Gargantext.Database.Query.Table.Node.Error (HasNodeError)
 import Gargantext.Database.Query.Table.Node.UpdateOpaleye (updateHyperdata)
-import Gargantext.Database.Prelude
 import Gargantext.Database.Schema.Node (node_hyperdata)
 import Gargantext.Prelude
-import Gargantext.Text.Metrics (Scored(..))
-import Gargantext.Viz.Chart
-import Gargantext.Viz.Types
+import Gargantext.Core.Text.Metrics (Scored(..), {-normalizeGlobal,-} normalizeLocal)
+import Gargantext.Core.Viz.Chart
+import Gargantext.Core.Viz.Types
+import qualified Gargantext.Database.Action.Metrics as Metrics
 
 -------------------------------------------------------------
 -- | Scatter metrics API
@@ -46,61 +50,358 @@ type ScatterAPI = Summary "SepGen IncExc metrics"
                   :> QueryParam  "list"       ListId
                   :> QueryParamR "ngramsType" TabType
                   :> QueryParam  "limit"      Int
-                  :> Get '[JSON] Metrics
+                  :> Get '[JSON] (HashedResponse Metrics)
+              :<|> Summary "Scatter update"
+                  :> QueryParam  "list"       ListId
+                  :> QueryParamR "ngramsType" TabType
+                  :> QueryParam  "limit"      Int
+                  :> Post '[JSON] ()
+              :<|> "hash" :> Summary "Scatter Hash"
+                          :> QueryParam  "list"       ListId
+                          :> QueryParamR "ngramsType" TabType
+                          :> Get '[JSON] Text
+
+scatterApi :: NodeId -> GargServer ScatterAPI
+scatterApi id' = getScatter id'
+            :<|> updateScatter id'
+            :<|> getScatterHash id'
 
 getScatter :: FlowCmdM env err m =>
+  CorpusId
+  -> Maybe ListId
+  -> TabType
+  -> Maybe Limit
+  -> m (HashedResponse Metrics)
+getScatter cId maybeListId tabType _maybeLimit = do
+  listId <- case maybeListId of
+    Just lid -> pure lid
+    Nothing  -> defaultList cId
+  node <- getNodeWith listId (Proxy :: Proxy HyperdataList)
+  let HyperdataList { _hl_scatter = scatterMap } = node ^. node_hyperdata
+      mChart = Map.lookup tabType scatterMap
+
+  chart <- case mChart of
+    Just chart -> pure chart
+    Nothing    -> do
+      updateScatter' cId maybeListId tabType Nothing
+
+  pure $ constructHashedResponse chart
+
+updateScatter :: FlowCmdM env err m =>
+  CorpusId
+  -> Maybe ListId
+  -> TabType
+  -> Maybe Limit
+  -> m ()
+updateScatter cId maybeListId tabType maybeLimit = do
+  printDebug "[updateScatter] cId" cId
+  printDebug "[updateScatter] maybeListId" maybeListId
+  printDebug "[updateScatter] tabType" tabType
+  printDebug "[updateScatter] maybeLimit" maybeLimit
+  _ <- updateScatter' cId maybeListId tabType maybeLimit
+  pure ()
+
+updateScatter' :: FlowCmdM env err m =>
   CorpusId
   -> Maybe ListId
   -> TabType
   -> Maybe Limit
   -> m Metrics
-getScatter cId maybeListId tabType maybeLimit = do
+updateScatter' cId maybeListId tabType maybeLimit = do
   (ngs', scores) <- Metrics.getMetrics cId maybeListId tabType maybeLimit
 
   let
-    metrics      = map (\(Scored t s1 s2) -> Metric t (log' 5 s1) (log' 2 s2) (listType t ngs')) scores
-    log' n x     = 1 + (if x <= 0 then 0 else (log $ (10^(n::Int)) * x))
+    metrics      = map (\(Scored t s1 s2) -> Metric t s1 s2 (listType t ngs'))
+                 $ map normalizeLocal scores
     listType t m = maybe (panic errorMsg) fst $ Map.lookup t m
     errorMsg     = "API.Node.metrics: key absent"
 
+  listId <- case maybeListId of
+    Just lid -> pure lid
+    Nothing  -> defaultList cId
+  node <- getNodeWith listId (Proxy :: Proxy HyperdataList)
+  let hl = node ^. node_hyperdata
+      scatterMap = hl ^. hl_scatter
+  _ <- updateHyperdata listId $ hl { _hl_scatter = Map.insert tabType (Metrics metrics) scatterMap }
+
   pure $ Metrics metrics
 
+getScatterHash :: FlowCmdM env err m =>
+  CorpusId
+  -> Maybe ListId
+  -> TabType
+  -> m Text
+getScatterHash cId maybeListId tabType = do
+  hash <$> getScatter cId maybeListId tabType Nothing
+
+
+-------------------------------------------------------------
+-- | Chart metrics API
+type ChartApi = Summary " Chart API"
+              :> QueryParam "from" UTCTime
+              :> QueryParam "to"   UTCTime
+              :> QueryParam  "list"       ListId
+              :> QueryParamR "ngramsType" TabType
+              :> Get '[JSON] (HashedResponse (ChartMetrics Histo))
+            :<|> Summary "Chart update"
+               :> QueryParam  "list"       ListId
+               :> QueryParamR "ngramsType" TabType
+               :> QueryParam  "limit"      Int
+               :> Post '[JSON] ()
+            :<|> "hash" :> Summary "Chart Hash"
+               :> QueryParam  "list"       ListId
+               :> QueryParamR "ngramsType" TabType
+               :> Get '[JSON] Text
+
+chartApi :: NodeId -> GargServer ChartApi
+chartApi id' = getChart id'
+          :<|> updateChart id'
+          :<|> getChartHash id'
 
 -- TODO add start / end
-getChart :: CorpusId -> Maybe UTCTime -> Maybe UTCTime -> Cmd err (ChartMetrics Histo)
-getChart cId _start _end = do
+getChart :: FlowCmdM env err m =>
+            CorpusId
+         -> Maybe UTCTime
+         -> Maybe UTCTime
+         -> Maybe ListId
+         -> TabType
+         -> m (HashedResponse (ChartMetrics Histo))
+getChart cId _start _end maybeListId tabType = do
+  listId <- case maybeListId of
+    Just lid -> pure lid
+    Nothing  -> defaultList cId
+  node <- getNodeWith listId (Proxy :: Proxy HyperdataList)
+  let chartMap = node ^. node_hyperdata ^. hl_chart
+      mChart = Map.lookup tabType chartMap
+
+  chart <- case mChart of
+    Just chart -> pure chart
+    Nothing    -> do
+      updateChart' cId maybeListId tabType Nothing
+
+  pure $ constructHashedResponse chart
+
+updateChart :: HasNodeError err =>
+  CorpusId
+  -> Maybe ListId
+  -> TabType
+  -> Maybe Limit
+  -> Cmd err ()
+updateChart cId maybeListId tabType maybeLimit = do
+  printDebug "[updateChart] cId" cId
+  printDebug "[updateChart] maybeListId" maybeListId
+  printDebug "[updateChart] tabType" tabType
+  printDebug "[updateChart] maybeLimit" maybeLimit
+  _ <- updateChart' cId maybeListId tabType maybeLimit
+  pure ()
+
+updateChart' :: HasNodeError err =>
+  CorpusId
+  -> Maybe ListId
+  -> TabType
+  -> Maybe Limit
+  -> Cmd err (ChartMetrics Histo)
+updateChart' cId maybeListId tabType _maybeLimit = do
+  listId <- case maybeListId of
+    Just lid -> pure lid
+    Nothing  -> defaultList cId
+  node <- getNodeWith listId (Proxy :: Proxy HyperdataList)
+  let hl = node ^. node_hyperdata
+      chartMap = hl ^. hl_chart
   h <- histoData cId
-  pure (ChartMetrics h)
+  _ <- updateHyperdata listId $ hl { _hl_chart = Map.insert tabType (ChartMetrics h) chartMap }
+
+  pure $ ChartMetrics h
+
+
+getChartHash :: FlowCmdM env err m =>
+  CorpusId
+  -> Maybe ListId
+  -> TabType
+  -> m Text
+getChartHash cId maybeListId tabType = do
+  hash <$> getChart cId Nothing Nothing maybeListId tabType
+-------------------------------------------------------------
+-- | Pie metrics API
+type PieApi = Summary "Pie Chart"
+           :> QueryParam "from" UTCTime
+           :> QueryParam "to"   UTCTime
+           :> QueryParam  "list"       ListId
+           :> QueryParamR "ngramsType" TabType
+           :> Get '[JSON] (HashedResponse (ChartMetrics Histo))
+         :<|> Summary "Pie Chart update"
+             :> QueryParam  "list"       ListId
+             :> QueryParamR "ngramsType" TabType
+             :> QueryParam  "limit"      Int
+             :> Post '[JSON] ()
+         :<|> "hash" :> Summary "Pie Hash"
+                     :> QueryParam  "list"       ListId
+                     :> QueryParamR "ngramsType" TabType
+                     :> Get '[JSON] Text
 
-getPie :: FlowCmdM env err m => CorpusId -> Maybe UTCTime -> Maybe UTCTime -> TabType -> m (ChartMetrics Histo)
-getPie cId _start _end tt = do
-  p <- pieData cId (ngramsTypeFromTabType tt) GraphTerm
-  pure (ChartMetrics p)
+pieApi :: NodeId -> GargServer PieApi
+pieApi id' = getPie id'
+        :<|> updatePie id'
+        :<|> getPieHash id'
 
-getTree :: FlowCmdM env err m => CorpusId -> Maybe UTCTime -> Maybe UTCTime -> TabType -> ListType -> m (ChartMetrics [MyTree])
-getTree cId _start _end tt lt = do
-  p <- treeData cId (ngramsTypeFromTabType tt) lt
-  pure (ChartMetrics p)
+getPie :: FlowCmdM env err m
+       => CorpusId
+       -> Maybe UTCTime
+       -> Maybe UTCTime
+       -> Maybe ListId
+       -> TabType
+       -> m (HashedResponse (ChartMetrics Histo))
+getPie cId _start _end maybeListId tabType = do
+  listId <- case maybeListId of
+    Just lid -> pure lid
+    Nothing  -> defaultList cId
+  node <- getNodeWith listId (Proxy :: Proxy HyperdataList)
+  let pieMap = node ^. node_hyperdata ^. hl_pie
+      mChart = Map.lookup tabType pieMap
 
+  chart <- case mChart of
+    Just chart -> pure chart
+    Nothing    -> do
+      updatePie' cId maybeListId tabType Nothing
 
+  pure $ constructHashedResponse chart
 
-updateChart :: FlowCmdM env err m =>
+updatePie :: FlowCmdM env err m =>
   CorpusId
   -> Maybe ListId
   -> TabType
   -> Maybe Limit
   -> m ()
-updateChart cId maybeListId _tabType _maybeLimit = do
+updatePie cId maybeListId tabType maybeLimit = do
+  printDebug "[updatePie] cId" cId
+  printDebug "[updatePie] maybeListId" maybeListId
+  printDebug "[updatePie] tabType" tabType
+  printDebug "[updatePie] maybeLimit" maybeLimit
+  _ <- updatePie' cId maybeListId tabType maybeLimit
+  pure ()
+
+updatePie' :: FlowCmdM env err m =>
+  CorpusId
+  -> Maybe ListId
+  -> TabType
+  -> Maybe Limit
+  -> m (ChartMetrics Histo)
+updatePie' cId maybeListId tabType _maybeLimit = do
   listId <- case maybeListId of
     Just lid -> pure lid
     Nothing  -> defaultList cId
-
   node <- getNodeWith listId (Proxy :: Proxy HyperdataList)
+  let hl = node ^. node_hyperdata
+      pieMap = hl ^. hl_pie
+
+  p <- chartData cId (ngramsTypeFromTabType tabType) MapTerm
+  _ <- updateHyperdata listId $ hl { _hl_pie = Map.insert tabType (ChartMetrics p) pieMap }
+
+  pure $ ChartMetrics p
+
+getPieHash :: FlowCmdM env err m =>
+  CorpusId
+  -> Maybe ListId
+  -> TabType
+  -> m Text
+getPieHash cId maybeListId tabType = do
+  hash <$> getPie cId Nothing Nothing maybeListId tabType
 
-  let (HyperdataList { hd_list = hdl }) = node ^. node_hyperdata
+-------------------------------------------------------------
+-- | Tree metrics API
+
+type TreeApi = Summary " Tree API"
+           :> QueryParam "from" UTCTime
+           :> QueryParam "to"   UTCTime
+           :> QueryParam  "list"       ListId
+           :> QueryParamR "ngramsType" TabType
+           :> QueryParamR "listType"   ListType
+           :> Get '[JSON] (HashedResponse (ChartMetrics [MyTree]))
+        :<|> Summary "Tree Chart update"
+                :> QueryParam  "list"       ListId
+                :> QueryParamR "ngramsType" TabType
+                :> QueryParamR "listType"   ListType
+                :> Post '[JSON] ()
+          :<|> "hash" :>
+                  Summary "Tree Hash"
+              :> QueryParam  "list"       ListId
+              :> QueryParamR "ngramsType" TabType
+              :> QueryParamR "listType"   ListType
+              :> Get '[JSON] Text
+
+                -- Depending on the Type of the Node, we could post
+                -- New documents for a corpus
+                -- New map list terms
+             -- :<|> "process"  :> MultipartForm MultipartData :> Post '[JSON] Text
+
+treeApi :: NodeId -> GargServer TreeApi
+treeApi id' = getTree id'
+         :<|> updateTree id'
+         :<|> getTreeHash id'
+
+getTree :: FlowCmdM env err m
+        => CorpusId
+        -> Maybe UTCTime
+        -> Maybe UTCTime
+        -> Maybe ListId
+        -> TabType
+        -> ListType
+        -> m (HashedResponse (ChartMetrics [MyTree]))
+getTree cId _start _end maybeListId tabType listType = do
+  listId <- case maybeListId of
+    Just lid -> pure lid
+    Nothing  -> defaultList cId
+
+  node <- getNodeWith listId (Proxy :: Proxy HyperdataList)
+  let treeMap = node ^. node_hyperdata ^. hl_tree
+      mChart = Map.lookup tabType treeMap
 
-  h <- histoData listId
+  chart <- case mChart of
+    Just chart -> pure chart
+    Nothing    -> do
+      updateTree' cId maybeListId tabType listType
 
-  _ <- updateHyperdata listId $ HyperdataList hdl $ Just $ ChartMetrics h
+  pure $ constructHashedResponse chart
 
+updateTree :: FlowCmdM env err m =>
+  CorpusId
+  -> Maybe ListId
+  -> TabType
+  -> ListType
+  -> m ()
+updateTree cId maybeListId tabType listType = do
+  printDebug "[updateTree] cId" cId
+  printDebug "[updateTree] maybeListId" maybeListId
+  printDebug "[updateTree] tabType" tabType
+  printDebug "[updateTree] listType" listType
+  _ <- updateTree' cId maybeListId tabType listType
   pure ()
+
+updateTree' :: FlowCmdM env err m =>
+  CorpusId
+  -> Maybe ListId
+  -> TabType
+  -> ListType
+  -> m (ChartMetrics [MyTree])
+updateTree' cId maybeListId tabType listType = do
+  listId <- case maybeListId of
+    Just lid -> pure lid
+    Nothing  -> defaultList cId
+
+  node <- getNodeWith listId (Proxy :: Proxy HyperdataList)
+  let hl = node ^. node_hyperdata
+      treeMap = hl ^. hl_tree
+  t <- treeData cId (ngramsTypeFromTabType tabType) listType
+  _ <- updateHyperdata listId $ hl { _hl_tree = Map.insert tabType (ChartMetrics t) treeMap }
+
+  pure $ ChartMetrics t
+
+getTreeHash :: FlowCmdM env err m =>
+  CorpusId
+  -> Maybe ListId
+  -> TabType
+  -> ListType
+  -> m Text
+getTreeHash cId maybeListId tabType listType = do
+  hash <$> getTree cId Nothing Nothing maybeListId tabType listType