Commit e00d9477 authored by Przemyslaw Kaminski's avatar Przemyslaw Kaminski

[list] updates for all list charts work

Still in TODO: refresh graph properly, show that it is updating
parent c9f9bba4
...@@ -2,7 +2,7 @@ module Gargantext.Components.Node ...@@ -2,7 +2,7 @@ module Gargantext.Components.Node
where where
import Gargantext.Prelude import Gargantext.Prelude
import Data.Argonaut (class DecodeJson, decodeJson, (.:)) import Data.Argonaut (class DecodeJson, decodeJson, (.:), (.:?), (.!=))
newtype NodePoly a = newtype NodePoly a =
NodePoly { id :: Int NodePoly { id :: Int
...@@ -29,7 +29,7 @@ instance decodeNodePoly :: (DecodeJson a) ...@@ -29,7 +29,7 @@ instance decodeNodePoly :: (DecodeJson a)
hyperdata <- obj .: "hyperdata" hyperdata <- obj .: "hyperdata"
hyperdata' <- decodeJson hyperdata hyperdata' <- decodeJson hyperdata
pure $ NodePoly { id : id pure $ NodePoly { id : id
, typename : typename , typename : typename
, userId : userId , userId : userId
, parentId : parentId , parentId : parentId
...@@ -38,11 +38,10 @@ instance decodeNodePoly :: (DecodeJson a) ...@@ -38,11 +38,10 @@ instance decodeNodePoly :: (DecodeJson a)
, hyperdata: hyperdata' , hyperdata: hyperdata'
} }
newtype HyperdataList = HyperdataList { preferences :: String} newtype HyperdataList = HyperdataList { preferences :: String }
instance decodeHyperdataList :: DecodeJson HyperdataList where instance decodeHyperdataList :: DecodeJson HyperdataList where
decodeJson json = do decodeJson json = do
obj <- decodeJson json obj <- decodeJson json
pref <- obj .: "preferences" pref <- obj .:? "preferences" .!= ""
pure $ HyperdataList { preferences : pref} pure $ HyperdataList { preferences : pref }
...@@ -17,7 +17,7 @@ import Gargantext.Components.Nodes.Corpus.Chart.Types (Path, Props) ...@@ -17,7 +17,7 @@ import Gargantext.Components.Nodes.Corpus.Chart.Types (Path, Props)
import Gargantext.Components.Nodes.Corpus.Chart.Utils as U import Gargantext.Components.Nodes.Corpus.Chart.Utils as U
import Gargantext.Routes (SessionRoute(..)) import Gargantext.Routes (SessionRoute(..))
import Gargantext.Sessions (Session, get) import Gargantext.Sessions (Session, get)
import Gargantext.Types (ChartType(..), CTabNgramType(..), TabType(..)) import Gargantext.Types (ChartType(..), TabType(..))
newtype ChartMetrics = ChartMetrics { "data" :: HistoMetrics } newtype ChartMetrics = ChartMetrics { "data" :: HistoMetrics }
...@@ -70,7 +70,7 @@ loaded :: Session -> Record Path -> R.State Int -> HistoMetrics -> R.Element ...@@ -70,7 +70,7 @@ loaded :: Session -> Record Path -> R.State Int -> HistoMetrics -> R.Element
loaded session path reload loaded = loaded session path reload loaded =
H.div {} [ H.div {} [
U.reloadButton reload U.reloadButton reload
, U.chartUpdateButton { chartType: Histo, ngramsType: CTabTerms, path, reload, session } , U.chartUpdateButton { chartType: Histo, path, reload, session }
, chart $ chartOptions loaded , chart $ chartOptions loaded
] ]
-- TODO: parametrize ngramsType above -- TODO: parametrize ngramsType above
...@@ -8,6 +8,7 @@ import Data.Maybe (Maybe(..)) ...@@ -8,6 +8,7 @@ import Data.Maybe (Maybe(..))
import Data.Tuple (Tuple(..)) import Data.Tuple (Tuple(..))
import Effect.Aff (Aff) import Effect.Aff (Aff)
import Reactix as R import Reactix as R
import Reactix.DOM.HTML as H
import Gargantext.Components.Charts.Options.ECharts (Options(..), chart, yAxis') import Gargantext.Components.Charts.Options.ECharts (Options(..), chart, yAxis')
import Gargantext.Components.Charts.Options.Type (xAxis) import Gargantext.Components.Charts.Options.Type (xAxis)
...@@ -20,7 +21,7 @@ import Gargantext.Components.Nodes.Corpus.Chart.Types (Path, Props) ...@@ -20,7 +21,7 @@ import Gargantext.Components.Nodes.Corpus.Chart.Types (Path, Props)
import Gargantext.Components.Nodes.Corpus.Chart.Utils as U import Gargantext.Components.Nodes.Corpus.Chart.Utils as U
import Gargantext.Routes (SessionRoute(..)) import Gargantext.Routes (SessionRoute(..))
import Gargantext.Sessions (Session, get) import Gargantext.Sessions (Session, get)
import Gargantext.Types (TabType, TermList(..)) import Gargantext.Types (ChartType(..), TabType, TermList(..))
newtype Metric = Metric newtype Metric = Metric
{ label :: String { label :: String
...@@ -102,5 +103,9 @@ metricsCpt = R.hooksComponent "G.C.N.C.C.M.metrics" cpt ...@@ -102,5 +103,9 @@ metricsCpt = R.hooksComponent "G.C.N.C.C.M.metrics" cpt
pure $ metricsLoadView {getMetrics, loaded, path, reload, session} pure $ metricsLoadView {getMetrics, loaded, path, reload, session}
loaded :: Session -> Record Path -> R.State Int -> Loaded -> R.Element loaded :: Session -> Record Path -> R.State Int -> Loaded -> R.Element
loaded _session _path setReload loaded = loaded session path reload loaded =
U.reloadButtonWrap setReload $ chart $ scatterOptions loaded H.div {} [
U.reloadButton reload
, U.chartUpdateButton { chartType: Scatter, path, reload, session }
, chart $ scatterOptions loaded
]
...@@ -9,6 +9,7 @@ import Data.String (take, joinWith, Pattern(..), split, length) ...@@ -9,6 +9,7 @@ import Data.String (take, joinWith, Pattern(..), split, length)
import Data.Tuple (Tuple(..)) import Data.Tuple (Tuple(..))
import Effect.Aff (Aff) import Effect.Aff (Aff)
import Reactix as R import Reactix as R
import Reactix.DOM.HTML as H
import Gargantext.Components.Charts.Options.ECharts (Options(..), chart, xAxis', yAxis') import Gargantext.Components.Charts.Options.ECharts (Options(..), chart, xAxis', yAxis')
import Gargantext.Components.Charts.Options.Series (seriesBarD1, seriesPieD1) import Gargantext.Components.Charts.Options.Series (seriesBarD1, seriesPieD1)
...@@ -87,8 +88,12 @@ pieCpt = R.hooksComponent "G.C.N.C.C.P.pie" cpt ...@@ -87,8 +88,12 @@ pieCpt = R.hooksComponent "G.C.N.C.C.P.pie" cpt
pure $ metricsLoadView {getMetrics, loaded: loadedPie, path, reload, session} pure $ metricsLoadView {getMetrics, loaded: loadedPie, path, reload, session}
loadedPie :: Session -> Record Path -> R.State Int -> HistoMetrics -> R.Element loadedPie :: Session -> Record Path -> R.State Int -> HistoMetrics -> R.Element
loadedPie _session _path setReload loaded = loadedPie session path reload loaded =
U.reloadButtonWrap setReload $ chart $ chartOptionsPie loaded H.div {} [
U.reloadButton reload
, U.chartUpdateButton { chartType: ChartPie, path, reload, session }
, chart $ chartOptionsPie loaded
]
bar :: Record Props -> R.Element bar :: Record Props -> R.Element
...@@ -102,5 +107,9 @@ barCpt = R.hooksComponent "LoadedMetricsBar" cpt ...@@ -102,5 +107,9 @@ barCpt = R.hooksComponent "LoadedMetricsBar" cpt
pure $ metricsLoadView {getMetrics, loaded: loadedBar, path, reload, session} pure $ metricsLoadView {getMetrics, loaded: loadedBar, path, reload, session}
loadedBar :: Session -> Record Path -> R.State Int -> Loaded -> R.Element loadedBar :: Session -> Record Path -> R.State Int -> Loaded -> R.Element
loadedBar _session _path setReload loaded = loadedBar session path reload loaded =
U.reloadButtonWrap setReload $ chart $ chartOptionsBar loaded H.div {} [
U.reloadButton reload
, U.chartUpdateButton { chartType: ChartBar, path, reload, session }
, chart $ chartOptionsBar loaded
]
...@@ -62,8 +62,9 @@ treeCpt = R.hooksComponent "G.C.N.C.C.T.tree" cpt ...@@ -62,8 +62,9 @@ treeCpt = R.hooksComponent "G.C.N.C.C.T.tree" cpt
pure $ metricsLoadView {getMetrics, loaded, path, reload, session} pure $ metricsLoadView {getMetrics, loaded, path, reload, session}
loaded :: Session -> Record Path -> R.State Int -> Loaded -> R.Element loaded :: Session -> Record Path -> R.State Int -> Loaded -> R.Element
loaded _session _path reload loaded = loaded session path reload loaded =
H.div {} [ H.div {} [
U.reloadButton reload U.reloadButton reload
, U.chartUpdateButton { chartType: ChartTree, path, reload, session }
, chart (scatterOptions loaded) , chart (scatterOptions loaded)
] ]
module Gargantext.Components.Nodes.Corpus.Chart.Utils where module Gargantext.Components.Nodes.Corpus.Chart.Utils where
import Data.Maybe (Maybe(..))
import Data.Tuple.Nested ((/\)) import Data.Tuple.Nested ((/\))
import DOM.Simple.Console (log2) import DOM.Simple.Console (log2)
import Effect (Effect) import Effect (Effect)
...@@ -32,7 +33,6 @@ reloadButton (_ /\ setReload) = H.a { className ...@@ -32,7 +33,6 @@ reloadButton (_ /\ setReload) = H.a { className
type ChartUpdateButtonProps = ( type ChartUpdateButtonProps = (
chartType :: T.ChartType chartType :: T.ChartType
, ngramsType :: T.CTabNgramType
, path :: Record Path , path :: Record Path
, reload :: R.State Int , reload :: R.State Int
, session :: Session , session :: Session
...@@ -45,7 +45,6 @@ chartUpdateButtonCpt :: R.Component ChartUpdateButtonProps ...@@ -45,7 +45,6 @@ chartUpdateButtonCpt :: R.Component ChartUpdateButtonProps
chartUpdateButtonCpt = R.hooksComponent "G.C.N.C.C.U.chartUpdateButton" cpt chartUpdateButtonCpt = R.hooksComponent "G.C.N.C.C.U.chartUpdateButton" cpt
where where
cpt { chartType cpt { chartType
, ngramsType
, path: { corpusId, listId, tabType } , path: { corpusId, listId, tabType }
, reload: (_ /\ setReload), session } _ = do , reload: (_ /\ setReload), session } _ = do
R.useEffect' $ do R.useEffect' $ do
...@@ -58,5 +57,15 @@ chartUpdateButtonCpt = R.hooksComponent "G.C.N.C.C.U.chartUpdateButton" cpt ...@@ -58,5 +57,15 @@ chartUpdateButtonCpt = R.hooksComponent "G.C.N.C.C.U.chartUpdateButton" cpt
onClick :: forall a. a -> Effect Unit onClick :: forall a. a -> Effect Unit
onClick _ = do onClick _ = do
launchAff_ $ do launchAff_ $ do
_ <- recomputeChart session chartType ngramsType corpusId listId case mNgramsType of
liftEffect $ setReload $ (_ + 1) Just ngramsType -> do
_ <- recomputeChart session chartType ngramsType corpusId listId
liftEffect $ setReload $ (_ + 1)
Nothing -> pure unit
mNgramsType = case tabType of
T.TabCorpus (T.TabNgramType ngramType) -> Just ngramType
T.TabCorpus _ -> Nothing
T.TabDocument (T.TabNgramType ngramType) -> Just ngramType
T.TabDocument _ -> Nothing
T.TabPairing _ -> Nothing
...@@ -118,7 +118,11 @@ sessionPath (R.Tab t i) = sessionPath (R.NodeAPI Node i (showTabType ...@@ -118,7 +118,11 @@ sessionPath (R.Tab t i) = sessionPath (R.NodeAPI Node i (showTabType
sessionPath (R.Children n o l s i) = sessionPath (R.NodeAPI Node i ("children?type=" <> show n <> offsetUrl o <> limitUrl l <> orderUrl s)) sessionPath (R.Children n o l s i) = sessionPath (R.NodeAPI Node i ("children?type=" <> show n <> offsetUrl o <> limitUrl l <> orderUrl s))
sessionPath (R.NodeAPI Phylo pId p) = "phyloscape?nodeId=" <> (show $ fromMaybe 0 pId) <> p sessionPath (R.NodeAPI Phylo pId p) = "phyloscape?nodeId=" <> (show $ fromMaybe 0 pId) <> p
sessionPath (R.RecomputeNgrams nt nId lId) = "node/" <> (show nId) <> "/ngrams/recompute?list=" <> (show lId) <> "&ngramsType=" <> (show nt) sessionPath (R.RecomputeNgrams nt nId lId) = "node/" <> (show nId) <> "/ngrams/recompute?list=" <> (show lId) <> "&ngramsType=" <> (show nt)
sessionPath (R.RecomputeListChart ChartBar nt nId lId) = "node/" <> (show nId) <> "/pie?list=" <> (show lId) <> "&ngramsType=" <> (show nt)
sessionPath (R.RecomputeListChart ChartPie nt nId lId) = "node/" <> (show nId) <> "/pie?list=" <> (show lId) <> "&ngramsType=" <> (show nt)
sessionPath (R.RecomputeListChart ChartTree nt nId lId) = "node/" <> (show nId) <> "/tree?list=" <> (show lId) <> "&ngramsType=" <> (show nt) <> "&listType=GraphTerm"
sessionPath (R.RecomputeListChart Histo nt nId lId) = "node/" <> (show nId) <> "/chart?list=" <> (show lId) <> "&ngramsType=" <> (show nt) sessionPath (R.RecomputeListChart Histo nt nId lId) = "node/" <> (show nId) <> "/chart?list=" <> (show lId) <> "&ngramsType=" <> (show nt)
sessionPath (R.RecomputeListChart Scatter nt nId lId) = "node/" <> (show nId) <> "/metrics?list=" <> (show lId) <> "&ngramsType=" <> (show nt)
sessionPath (R.RecomputeListChart _ nt nId lId) = "node/" <> (show nId) <> "/recompute-chart?list=" <> (show lId) <> "&ngramsType=" <> (show nt) sessionPath (R.RecomputeListChart _ nt nId lId) = "node/" <> (show nId) <> "/recompute-chart?list=" <> (show lId) <> "&ngramsType=" <> (show nt)
sessionPath (R.GraphAPI gId p) = "graph/" <> (show gId) <> "/" <> p sessionPath (R.GraphAPI gId p) = "graph/" <> (show gId) <> "/" <> p
sessionPath (R.GetNgrams opts i) = sessionPath (R.GetNgrams opts i) =
......
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