Commit c9f9bba4 authored by Przemyslaw Kaminski's avatar Przemyslaw Kaminski

[list] recompute histo chart button

parent cdf79c7d
{
"name": "Gargantext",
"version": "0.0.1.4.2",
"version": "0.0.1.5.1",
"scripts": {
"rebase-set": "spago package-set-upgrade && spago psc-package-insdhall",
"rebuild-set": "spago psc-package-insdhall",
......
module Gargantext.Components.Nodes.Corpus.Chart.API where
import Effect.Aff (Aff)
import Gargantext.Prelude
import Gargantext.Routes (SessionRoute(..))
import Gargantext.Sessions (Session, post)
import Gargantext.Types as T
recomputeChart :: Session -> T.ChartType -> T.CTabNgramType -> Int -> Int -> Aff (Array Int)
recomputeChart session chartType ngramType corpusId listId =
post session (RecomputeListChart chartType ngramType corpusId listId) {}
......@@ -17,7 +17,7 @@ import Gargantext.Components.Nodes.Corpus.Chart.Types (Path, Props)
import Gargantext.Components.Nodes.Corpus.Chart.Utils as U
import Gargantext.Routes (SessionRoute(..))
import Gargantext.Sessions (Session, get)
import Gargantext.Types (ChartType(..), TabType)
import Gargantext.Types (ChartType(..), CTabNgramType(..), TabType(..))
newtype ChartMetrics = ChartMetrics { "data" :: HistoMetrics }
......@@ -70,6 +70,7 @@ loaded :: Session -> Record Path -> R.State Int -> HistoMetrics -> R.Element
loaded session path reload loaded =
H.div {} [
U.reloadButton reload
, U.chartUpdateButton { chartType: Histo, path, reload, session }
, U.chartUpdateButton { chartType: Histo, ngramsType: CTabTerms, path, reload, session }
, chart $ chartOptions loaded
]
-- TODO: parametrize ngramsType above
......@@ -3,11 +3,14 @@ module Gargantext.Components.Nodes.Corpus.Chart.Utils where
import Data.Tuple.Nested ((/\))
import DOM.Simple.Console (log2)
import Effect (Effect)
import Effect.Aff (launchAff_)
import Effect.Class (liftEffect)
import Effect.Uncurried (mkEffectFn1)
import Reactix as R
import Reactix.DOM.HTML as H
import Gargantext.Prelude
import Gargantext.Components.Nodes.Corpus.Chart.API (recomputeChart)
import Gargantext.Components.Nodes.Corpus.Chart.Types (Path)
import Gargantext.Sessions (Session)
import Gargantext.Types as T
......@@ -29,6 +32,7 @@ reloadButton (_ /\ setReload) = H.a { className
type ChartUpdateButtonProps = (
chartType :: T.ChartType
, ngramsType :: T.CTabNgramType
, path :: Record Path
, reload :: R.State Int
, session :: Session
......@@ -40,7 +44,10 @@ chartUpdateButton p = R.createElement chartUpdateButtonCpt p []
chartUpdateButtonCpt :: R.Component ChartUpdateButtonProps
chartUpdateButtonCpt = R.hooksComponent "G.C.N.C.C.U.chartUpdateButton" cpt
where
cpt { chartType, path: { corpusId, listId, tabType }, reload: (_ /\ setReload), session } _ = do
cpt { chartType
, ngramsType
, path: { corpusId, listId, tabType }
, reload: (_ /\ setReload), session } _ = do
R.useEffect' $ do
log2 "[chartUpdateButton] tabType" tabType
......@@ -50,4 +57,6 @@ chartUpdateButtonCpt = R.hooksComponent "G.C.N.C.C.U.chartUpdateButton" cpt
where
onClick :: forall a. a -> Effect Unit
onClick _ = do
setReload $ (_ + 1)
launchAff_ $ do
_ <- recomputeChart session chartType ngramsType corpusId listId
liftEffect $ setReload $ (_ + 1)
......@@ -2,6 +2,7 @@ module Gargantext.Components.Nodes.Lists.Tabs where
import Data.Maybe (Maybe(..), fromMaybe)
import Data.Tuple.Nested ((/\))
import DOM.Simple.Console (log2)
import Reactix as R
import Reactix.DOM.HTML as H
......@@ -47,8 +48,15 @@ ngramsView props = R.createElement ngramsViewCpt props []
ngramsViewCpt :: R.Component NgramsViewProps
ngramsViewCpt = R.hooksComponent "G.C.N.L.T.ngramsView" cpt
where
cpt {mode, session, corpusId, corpusData: {defaultListId}} _ = do
chartType <- R.useState' Scatter
cpt { corpusData: {defaultListId}
, corpusId
, mode
, session } _ = do
R.useEffect' $ do
log2 "[ngramsViewCpt] corpusId" corpusId
log2 "[ngramsViewCpt] defaultListId" defaultListId
chartType <- R.useState' Histo
pure $ R.fragment
( charts tabNgramType chartType
......@@ -60,15 +68,15 @@ ngramsViewCpt = R.hooksComponent "G.C.N.L.T.ngramsView" cpt
where
tabNgramType = modeTabType mode
tabType = TabCorpus (TabNgramType tabNgramType)
listId = 0 -- TODO!
listId = defaultListId
path = {corpusId, listId, tabType, limit: (Just 1000)}
charts CTabTerms (chartType /\ setChartType) = [
H.div { className: "row" } [
H.div { className: "row chart-type-selector" } [
H.div { className: "col-md-3" } [
R2.select { className: "form-control"
, on: { change: \e -> setChartType $ const $ fromMaybe Scatter $ chartTypeFromString $ R2.unsafeEventValue e }
, on: { change: \e -> setChartType $ const $ fromMaybe Histo $ chartTypeFromString $ R2.unsafeEventValue e }
, defaultValue: show chartType } [
H.option { value: show Histo } [ H.text $ show Histo ]
, H.option { value: show Scatter } [ H.text $ show Scatter ]
......
......@@ -118,8 +118,8 @@ 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.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.RecomputeListChart Histo nId lId) = "node/" <> (show nId) <> "/chart?list=" <> (show lId)
sessionPath (R.RecomputeListChart _ nId lId) = "node/" <> (show nId) <> "/recompute-chart?list=" <> (show lId)
sessionPath (R.RecomputeListChart Histo nt nId lId) = "node/" <> (show nId) <> "/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.GetNgrams opts i) =
base opts.tabType
......
......@@ -37,7 +37,7 @@ data SessionRoute
| PutNgrams TabType (Maybe ListId) (Maybe TermList) (Maybe Id)
-- ^ This name is not good. In particular this URL is used both in PUT and POST.
| RecomputeNgrams (TabSubType CTabNgramType) Id ListId
| RecomputeListChart ChartType Id ListId
| RecomputeListChart ChartType CTabNgramType Id ListId
| NodeAPI NodeType (Maybe Id) String
| GraphAPI Id String
| ListsRoute ListId
......
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