Commit 42b94fad authored by Alexandre Delanoë's avatar Alexandre Delanoë

Merge branch 'dev-doc-table-optimization' of...

Merge branch 'dev-doc-table-optimization' of ssh://gitlab.iscpif.fr:20022/gargantext/haskell-gargantext into dev-merge
parents 89c9ae26 50fb44bf
Pipeline #970 failed with stage
...@@ -3,6 +3,7 @@ module Gargantext.API.HashedResponse where ...@@ -3,6 +3,7 @@ module Gargantext.API.HashedResponse where
import Data.Aeson import Data.Aeson
import Data.Swagger import Data.Swagger
import Data.Text (Text) import Data.Text (Text)
import Gargantext.Prelude import Gargantext.Prelude
import qualified Gargantext.Prelude.Utils as Crypto (hash) import qualified Gargantext.Prelude.Utils as Crypto (hash)
import GHC.Generics (Generic) import GHC.Generics (Generic)
...@@ -15,4 +16,4 @@ instance ToJSON a => ToJSON (HashedResponse a) where ...@@ -15,4 +16,4 @@ instance ToJSON a => ToJSON (HashedResponse a) where
toJSON = genericToJSON defaultOptions toJSON = genericToJSON defaultOptions
constructHashedResponse :: ToJSON a => a -> HashedResponse a constructHashedResponse :: ToJSON a => a -> HashedResponse a
constructHashedResponse v = HashedResponse (Crypto.hash $ encode v) v constructHashedResponse v = HashedResponse { hash = Crypto.hash $ encode v, value = v }
...@@ -19,8 +19,11 @@ module Gargantext.API.Metrics ...@@ -19,8 +19,11 @@ module Gargantext.API.Metrics
where where
import Control.Lens import Control.Lens
import qualified Data.Map as Map
import Data.Time (UTCTime) import Data.Time (UTCTime)
import Data.Text (Text) import Data.Text (Text)
import Servant
import Gargantext.API.HashedResponse import Gargantext.API.HashedResponse
import Gargantext.API.Ngrams import Gargantext.API.Ngrams
import Gargantext.API.Ngrams.NTree import Gargantext.API.Ngrams.NTree
...@@ -39,8 +42,6 @@ import Gargantext.Prelude ...@@ -39,8 +42,6 @@ import Gargantext.Prelude
import Gargantext.Text.Metrics (Scored(..)) import Gargantext.Text.Metrics (Scored(..))
import Gargantext.Viz.Chart import Gargantext.Viz.Chart
import Gargantext.Viz.Types import Gargantext.Viz.Types
import Servant
import qualified Data.Map as Map
import qualified Gargantext.Database.Action.Metrics as Metrics import qualified Gargantext.Database.Action.Metrics as Metrics
------------------------------------------------------------- -------------------------------------------------------------
...@@ -115,11 +116,8 @@ updateScatter' cId maybeListId tabType maybeLimit = do ...@@ -115,11 +116,8 @@ updateScatter' cId maybeListId tabType maybeLimit = do
Just lid -> pure lid Just lid -> pure lid
Nothing -> defaultList cId Nothing -> defaultList cId
node <- getNodeWith listId (Proxy :: Proxy HyperdataList) node <- getNodeWith listId (Proxy :: Proxy HyperdataList)
let HyperdataList { _hl_chart = hdc let hl = node ^. node_hyperdata
, _hl_list = hdl _ <- updateHyperdata listId $ hl { _hl_scatter = Just $ Metrics metrics }
, _hl_pie = hdp
, _hl_tree = hdt } = node ^. node_hyperdata
_ <- updateHyperdata listId $ HyperdataList hdc hdl hdp (Just $ Metrics metrics) hdt
pure $ Metrics metrics pure $ Metrics metrics
...@@ -128,7 +126,7 @@ getScatterHash :: FlowCmdM env err m => ...@@ -128,7 +126,7 @@ getScatterHash :: FlowCmdM env err m =>
-> Maybe ListId -> Maybe ListId
-> TabType -> TabType
-> m Text -> m Text
getScatterHash cId maybeListId tabType = getScatterHash cId maybeListId tabType = do
hash <$> getScatter cId maybeListId tabType Nothing hash <$> getScatter cId maybeListId tabType Nothing
...@@ -199,12 +197,9 @@ updateChart' cId maybeListId _tabType _maybeLimit = do ...@@ -199,12 +197,9 @@ updateChart' cId maybeListId _tabType _maybeLimit = do
Just lid -> pure lid Just lid -> pure lid
Nothing -> defaultList cId Nothing -> defaultList cId
node <- getNodeWith listId (Proxy :: Proxy HyperdataList) node <- getNodeWith listId (Proxy :: Proxy HyperdataList)
let HyperdataList { _hl_list = hdl let hl = node ^. node_hyperdata
, _hl_pie = hdp
, _hl_scatter = hds
, _hl_tree = hdt } = node ^. node_hyperdata
h <- histoData cId h <- histoData cId
_ <- updateHyperdata listId $ HyperdataList (Just $ ChartMetrics h) hdl hdp hds hdt _ <- updateHyperdata listId $ hl { _hl_chart = Just $ ChartMetrics h }
pure $ ChartMetrics h pure $ ChartMetrics h
...@@ -214,9 +209,9 @@ getChartHash :: FlowCmdM env err m => ...@@ -214,9 +209,9 @@ getChartHash :: FlowCmdM env err m =>
-> Maybe ListId -> Maybe ListId
-> TabType -> TabType
-> m Text -> m Text
getChartHash cId maybeListId tabType = getChartHash cId maybeListId tabType = do
hash <$> getChart cId Nothing Nothing maybeListId tabType hash <$> getChart cId Nothing Nothing maybeListId tabType
------------------------------------------------------------- -------------------------------------------------------------
-- | Pie metrics API -- | Pie metrics API
type PieApi = Summary "Pie Chart" type PieApi = Summary "Pie Chart"
...@@ -283,13 +278,10 @@ updatePie' cId maybeListId tabType _maybeLimit = do ...@@ -283,13 +278,10 @@ updatePie' cId maybeListId tabType _maybeLimit = do
Just lid -> pure lid Just lid -> pure lid
Nothing -> defaultList cId Nothing -> defaultList cId
node <- getNodeWith listId (Proxy :: Proxy HyperdataList) node <- getNodeWith listId (Proxy :: Proxy HyperdataList)
let HyperdataList { _hl_chart = hdc let hl = node ^. node_hyperdata
, _hl_list = hdl
, _hl_scatter = hds
, _hl_tree = hdt } = node ^. node_hyperdata
p <- pieData cId (ngramsTypeFromTabType tabType) MapTerm p <- pieData cId (ngramsTypeFromTabType tabType) MapTerm
_ <- updateHyperdata listId $ HyperdataList hdc hdl (Just $ ChartMetrics p) hds hdt _ <- updateHyperdata listId $ hl { _hl_pie = Just $ ChartMetrics p }
pure $ ChartMetrics p pure $ ChartMetrics p
...@@ -298,7 +290,7 @@ getPieHash :: FlowCmdM env err m => ...@@ -298,7 +290,7 @@ getPieHash :: FlowCmdM env err m =>
-> Maybe ListId -> Maybe ListId
-> TabType -> TabType
-> m Text -> m Text
getPieHash cId maybeListId tabType = getPieHash cId maybeListId tabType = do
hash <$> getPie cId Nothing Nothing maybeListId tabType hash <$> getPie cId Nothing Nothing maybeListId tabType
------------------------------------------------------------- -------------------------------------------------------------
...@@ -378,12 +370,9 @@ updateTree' cId maybeListId tabType listType = do ...@@ -378,12 +370,9 @@ updateTree' cId maybeListId tabType listType = do
Nothing -> defaultList cId Nothing -> defaultList cId
node <- getNodeWith listId (Proxy :: Proxy HyperdataList) node <- getNodeWith listId (Proxy :: Proxy HyperdataList)
let HyperdataList { _hl_chart = hdc let hl = node ^. node_hyperdata
, _hl_list = hdl
, _hl_scatter = hds
, _hl_pie = hdp } = node ^. node_hyperdata
t <- treeData cId (ngramsTypeFromTabType tabType) listType t <- treeData cId (ngramsTypeFromTabType tabType) listType
_ <- updateHyperdata listId $ HyperdataList hdc hdl hdp hds (Just $ ChartMetrics t) _ <- updateHyperdata listId $ hl { _hl_tree = Just $ ChartMetrics t }
pure $ ChartMetrics t pure $ ChartMetrics t
...@@ -393,5 +382,5 @@ getTreeHash :: FlowCmdM env err m => ...@@ -393,5 +382,5 @@ getTreeHash :: FlowCmdM env err m =>
-> TabType -> TabType
-> ListType -> ListType
-> m Text -> m Text
getTreeHash cId maybeListId tabType listType = getTreeHash cId maybeListId tabType listType = do
hash <$> getTree cId Nothing Nothing maybeListId tabType listType hash <$> getTree cId Nothing Nothing maybeListId tabType listType
...@@ -56,8 +56,8 @@ instance ToJSON a => MimeRender HTML a where ...@@ -56,8 +56,8 @@ instance ToJSON a => MimeRender HTML a where
------------------------------------------------------------------------ ------------------------------------------------------------------------
get :: RepoCmdM env err m get :: RepoCmdM env err m =>
=> ListId -> m (Headers '[Header "Content-Disposition" Text] NgramsList) ListId -> m (Headers '[Header "Content-Disposition" Text] NgramsList)
get lId = do get lId = do
lst <- get' lId lst <- get' lId
let (NodeId id) = lId let (NodeId id) = lId
...@@ -108,17 +108,17 @@ postAsync' :: FlowCmdM env err m ...@@ -108,17 +108,17 @@ postAsync' :: FlowCmdM env err m
postAsync' l (WithFile _ m _) logStatus = do postAsync' l (WithFile _ m _) logStatus = do
logStatus JobLog { _scst_succeeded = Just 0 logStatus JobLog { _scst_succeeded = Just 0
, _scst_failed = Just 0 , _scst_failed = Just 0
, _scst_remaining = Just 1 , _scst_remaining = Just 1
, _scst_events = Just [] , _scst_events = Just []
} }
_r <- post l m _r <- post l m
pure JobLog { _scst_succeeded = Just 1 pure JobLog { _scst_succeeded = Just 1
, _scst_failed = Just 0 , _scst_failed = Just 0
, _scst_remaining = Just 0 , _scst_remaining = Just 0
, _scst_events = Just [] , _scst_events = Just []
} }
data WithFile = WithFile data WithFile = WithFile
{ _wf_filetype :: !FileType { _wf_filetype :: !FileType
......
Markdown is supported
0% or
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment