Commit d5c0d7a3 authored by Przemyslaw Kaminski's avatar Przemyslaw Kaminski

[list] add option to pick charts for ngram table

parent 09b7b48c
module Gargantext.Components.Nodes.Corpus.Chart where
import Data.Maybe (Maybe(..))
import Reactix as R
import Gargantext.Components.Nodes.Corpus.Chart.Histo (histo)
import Gargantext.Components.Nodes.Corpus.Chart.Metrics (metrics)
import Gargantext.Components.Nodes.Corpus.Chart.Pie (pie, bar)
import Gargantext.Components.Nodes.Corpus.Chart.Tree (tree)
import Gargantext.Components.Nodes.Corpus.Chart.Types (Path, ListPath, Props)
import Gargantext.Types (ChartType(..))
getChartFunction :: ChartType -> Maybe (Record (Props Path) -> R.Element)
getChartFunction Histo = Just histo
getChartFunction ChartBar = Just bar
getChartFunction ChartPie = Just pie
getChartFunction _ = Nothing
getChartFunctionWithList :: ChartType -> Maybe (Record (Props ListPath) -> R.Element)
getChartFunctionWithList Scatter = Just metrics
getChartFunctionWithList ChartTree = Just tree
getChartFunctionWithList _ = Nothing
......@@ -11,16 +11,13 @@ import Gargantext.Components.Charts.Options.Series (seriesBarD1)
import Gargantext.Components.Charts.Options.Color (grey)
import Gargantext.Components.Charts.Options.Font (itemStyle, mkTooltip, templateFormatter)
import Gargantext.Components.Charts.Options.Data (dataSerie)
import Gargantext.Components.Nodes.Corpus.Chart.Types (Path, Props)
import Gargantext.Hooks.Loader (useLoader)
import Gargantext.Components.Nodes.Corpus.Chart.Utils as U
import Gargantext.Routes (SessionRoute(..))
import Gargantext.Sessions (Session, get)
import Gargantext.Types (ChartType(..), TabType)
type Path = { corpusId :: Int, tabType :: TabType }
type Props = ( path :: Path, session :: Session )
newtype ChartMetrics = ChartMetrics { "data" :: HistoMetrics }
instance decodeChartMetrics :: DecodeJson ChartMetrics where
......@@ -51,23 +48,23 @@ chartOptions (HistoMetrics { dates: dates', count: count'}) = Options
, series : [seriesBarD1 {name: "Number of publication / year"} $
map (\n -> dataSerie {value: n, itemStyle : itemStyle {color:grey}}) count'] }
getMetrics :: Session -> Path -> Aff HistoMetrics
getMetrics :: Session -> Record Path -> Aff HistoMetrics
getMetrics session {corpusId, tabType} = do
ChartMetrics ms <- get session chart
pure ms."data"
where chart = Chart {chartType: Histo, tabType: tabType} (Just corpusId)
histo :: Record Props -> R.Element
histo :: Record (Props Path) -> R.Element
histo props = R.createElement histoCpt props []
histoCpt :: R.Component Props
histoCpt :: R.Component (Props Path)
histoCpt = R.hooksComponent "LoadedMetricsHisto" cpt
where
cpt {session,path} _ = do
setReload <- R.useState' 0
pure $ metricsLoadView session setReload path
metricsLoadView :: Session -> R.State Int -> Path -> R.Element
metricsLoadView :: Session -> R.State Int -> Record Path -> R.Element
metricsLoadView s setReload p = R.createElement el {session: s, path: p} []
where
el = R.hooksComponent "MetricsLoadedHistoView" cpt
......
......@@ -15,21 +15,13 @@ import Gargantext.Components.Charts.Options.Series (Series, seriesScatterD2)
import Gargantext.Components.Charts.Options.Color (green, grey, red)
import Gargantext.Components.Charts.Options.Font (itemStyle, mkTooltip, templateFormatter)
import Gargantext.Components.Charts.Options.Data (dataSerie)
import Gargantext.Components.Nodes.Corpus.Chart.Types (ListPath, Props)
import Gargantext.Hooks.Loader (useLoader)
import Gargantext.Components.Nodes.Corpus.Chart.Utils as U
import Gargantext.Routes (SessionRoute(..))
import Gargantext.Sessions (Session, get)
import Gargantext.Types (TabType, TermList(..))
type Path =
{ corpusId :: Int
, listId :: Int
, tabType :: TabType
, limit :: Maybe Int
}
type Props = ( path :: Path, session :: Session )
newtype Metric = Metric
{ label :: String
, x :: Number
......@@ -92,23 +84,23 @@ scatterOptions metrics' = Options
}
--}
getMetrics :: Session -> Path -> Aff Loaded
getMetrics :: Session -> Record ListPath -> Aff Loaded
getMetrics session {corpusId, listId, limit, tabType} = do
Metrics ms <- get session metrics'
pure ms."data"
where metrics' = CorpusMetrics {listId, tabType, limit} (Just corpusId)
metrics :: Record Props -> R.Element
metrics :: Record (Props ListPath) -> R.Element
metrics props = R.createElement metricsCpt props []
metricsCpt :: R.Component Props
metricsCpt :: R.Component (Props ListPath)
metricsCpt = R.hooksComponent "LoadedMetrics" cpt
where
cpt {path, session} _ = do
setReload <- R.useState' 0
pure $ metricsLoadView session setReload path
metricsLoadView :: Session -> R.State Int -> Path -> R.Element
metricsLoadView :: Session -> R.State Int -> Record ListPath -> R.Element
metricsLoadView s setReload p = R.createElement el {session: s, path: p} []
where
el = R.hooksComponent "MetricsLoadedView" cpt
......
......@@ -15,19 +15,13 @@ import Gargantext.Components.Charts.Options.Series (seriesBarD1, seriesPieD1)
import Gargantext.Components.Charts.Options.Color (blue)
import Gargantext.Components.Charts.Options.Font (itemStyle, mkTooltip, templateFormatter)
import Gargantext.Components.Charts.Options.Data (dataSerie)
import Gargantext.Components.Nodes.Corpus.Chart.Types (Path, Props)
import Gargantext.Hooks.Loader (useLoader)
import Gargantext.Components.Nodes.Corpus.Chart.Utils as U
import Gargantext.Routes (SessionRoute(..))
import Gargantext.Sessions (Session, get)
import Gargantext.Types (ChartType(..), TabType)
type Path =
{ corpusId :: Int
, tabType :: TabType
}
type Props = ( session :: Session, path :: Path )
newtype ChartMetrics = ChartMetrics
{ "data" :: HistoMetrics
}
......@@ -76,23 +70,23 @@ chartOptionsPie (HistoMetrics { dates: dates', count: count'}) = Options
}
getMetrics :: Session -> Path -> Aff HistoMetrics
getMetrics :: Session -> Record Path -> Aff HistoMetrics
getMetrics session {corpusId, tabType:tabType} = do
ChartMetrics ms <- get session chart
pure ms."data"
where chart = Chart {chartType: ChartPie, tabType: tabType} (Just corpusId)
pie :: Record Props -> R.Element
pie :: Record (Props Path) -> R.Element
pie props = R.createElement pieCpt props []
pieCpt :: R.Component Props
pieCpt :: R.Component (Props Path)
pieCpt = R.hooksComponent "LoadedMetricsPie" cpt
where
cpt {path,session} _ = do
setReload <- R.useState' 0
pure $ metricsLoadPieView session setReload path
metricsLoadPieView :: Session -> R.State Int -> Path -> R.Element
metricsLoadPieView :: Session -> R.State Int -> Record Path -> R.Element
metricsLoadPieView s setReload p = R.createElement el {session: s,path: p} []
where
el = R.hooksComponent "MetricsLoadedPieView" cpt
......@@ -104,10 +98,10 @@ loadedMetricsPieView :: R.State Int -> HistoMetrics -> R.Element
loadedMetricsPieView setReload loaded = U.reloadButtonWrap setReload $ chart $ chartOptionsPie loaded
bar :: Record Props -> R.Element
bar :: Record (Props Path) -> R.Element
bar props = R.createElement barCpt props []
barCpt :: R.Component Props
barCpt :: R.Component (Props Path)
barCpt = R.hooksComponent "LoadedMetricsBar" cpt
where
cpt {path, session} _ = do
......@@ -115,7 +109,7 @@ barCpt = R.hooksComponent "LoadedMetricsBar" cpt
pure $ metricsLoadBarView session setReload path
metricsLoadBarView :: Session -> R.State Int -> Path -> R.Element
metricsLoadBarView :: Session -> R.State Int -> Record Path -> R.Element
metricsLoadBarView s setReload p = R.createElement el {path: p, session: s} []
where
el = R.hooksComponent "MetricsLoadedBarView" cpt
......
......@@ -10,20 +10,13 @@ import Reactix.DOM.HTML as H
import Gargantext.Components.Charts.Options.ECharts (Options(..), chart, xAxis', yAxis')
import Gargantext.Components.Charts.Options.Series (TreeNode, Trees(..), mkTree)
import Gargantext.Components.Charts.Options.Font (mkTooltip, templateFormatter)
import Gargantext.Hooks.Loader (useLoader)
import Gargantext.Components.Nodes.Corpus.Chart.Utils as U
import Gargantext.Components.Nodes.Corpus.Chart.Types (ListPath, Props)
import Gargantext.Hooks.Loader (useLoader)
import Gargantext.Routes (SessionRoute(..))
import Gargantext.Sessions (Session, get)
import Gargantext.Types (ChartType(..), TabType)
type Path =
{ corpusId :: Int
, listId :: Int
, tabType :: TabType
, limit :: Maybe Int
}
type Props = ( path :: Path, session :: Session )
newtype Metrics = Metrics
{ "data" :: Array TreeNode
}
......@@ -50,24 +43,24 @@ scatterOptions nodes = Options
}
getMetrics :: Session -> Path -> Aff Loaded
getMetrics :: Session -> Record ListPath -> Aff Loaded
getMetrics session {corpusId, listId, limit, tabType} = do
Metrics ms <- get session chart
pure ms."data"
where
chart = Chart {chartType : ChartTree, tabType: tabType} (Just corpusId)
tree :: Record Props -> R.Element
tree :: Record (Props ListPath) -> R.Element
tree props = R.createElement treeCpt props []
treeCpt :: R.Component Props
treeCpt :: R.Component (Props ListPath)
treeCpt = R.hooksComponent "LoadedMetrics" cpt
where
cpt {path, session} _ = do
setReload <- R.useState' 0
pure $ metricsLoadView session setReload path
metricsLoadView :: Session -> R.State Int -> Path -> R.Element
metricsLoadView :: Session -> R.State Int -> Record ListPath -> R.Element
metricsLoadView session setReload path = R.createElement el path []
where
el = R.hooksComponent "MetricsLoadView" cpt
......
module Gargantext.Components.Nodes.Corpus.Chart.Types where
import Data.Maybe (Maybe)
import Gargantext.Sessions (Session)
import Gargantext.Types (TabType)
type Path = (
corpusId :: Int
, tabType :: TabType
)
type ListPath = (
limit :: Maybe Int
, listId :: Int
| Path
)
type Props a = ( path :: Record a, session :: Session )
module Gargantext.Components.Nodes.Lists.Tabs where
import Prelude
import Data.Maybe (Maybe(..))
import Data.Maybe (Maybe(..), maybe)
import Data.Tuple.Nested ((/\))
import Reactix as R
import Reactix.DOM.HTML as H
import Gargantext.Prelude
import Gargantext.Components.NgramsTable as NT
import Gargantext.Components.Tab as Tab
import Gargantext.Components.Nodes.Corpus.Types (CorpusData)
import Gargantext.Components.Nodes.Corpus.Chart.Metrics (metrics)
import Gargantext.Components.Nodes.Corpus.Chart.Pie (pie, bar)
import Gargantext.Components.Nodes.Corpus.Chart.Tree (tree)
import Gargantext.Components.Nodes.Corpus.Chart (getChartFunctionWithList)
import Gargantext.Sessions (Session)
import Gargantext.Types (Mode(..), TabSubType(..), TabType(..), modeTabType)
import Gargantext.Types (ChartType(..), CTabNgramType(..), Mode(..), TabSubType(..), TabType(..), chartTypeFromString, modeTabType)
import Gargantext.Utils.Reactix as R2
type Props =
( session :: Session
......@@ -22,7 +27,7 @@ tabs :: Record Props -> R.Element
tabs props = R.createElement tabsCpt props []
tabsCpt :: R.Component Props
tabsCpt = R.hooksComponent "CorpusTabs" cpt
tabsCpt = R.hooksComponent "G.C.N.L.T.tabs" cpt
where
cpt {session, corpusId, corpusData: corpusData@{defaultListId}} _ = do
(selected /\ setSelected) <- R.useState' 0
......@@ -40,20 +45,35 @@ ngramsView :: Record NgramsViewProps -> R.Element
ngramsView props = R.createElement ngramsViewCpt props []
ngramsViewCpt :: R.Component NgramsViewProps
ngramsViewCpt = R.staticComponent "ListsNgramsView" cpt
ngramsViewCpt = R.hooksComponent "G.C.N.L.T.ngramsView" cpt
where
cpt {mode, session, corpusId, corpusData: {defaultListId}} _ =
R.fragment
[ chart mode
, NT.mainNgramsTable
cpt {mode, session, corpusId, corpusData: {defaultListId}} _ = do
chartType <- R.useState' Scatter
pure $ R.fragment
( charts tabNgramType chartType
<> [
NT.mainNgramsTable
{session, defaultListId, nodeId: corpusId, tabType, tabNgramType, withAutoUpdate: false}
]
)
where
tabNgramType = modeTabType mode
tabType = TabCorpus (TabNgramType tabNgramType)
listId = 0 -- TODO!
path = {corpusId, tabType}
path2 = {corpusId, listId, tabType, limit: (Just 1000)} -- todo
charts CTabTerms (chartType /\ setChartType) = [
maybe metrics identity (getChartFunctionWithList chartType) $ { session, path: path2 }
, R2.select { on: { change: \e -> setChartType $ const $ maybe Scatter identity $ chartTypeFromString $ R2.unsafeEventValue e }
, defaultValue: show chartType } [
H.option { value: show Scatter } [ H.text $ show Scatter ]
, H.option { value: show ChartTree } [ H.text $ show ChartTree ]
]
]
charts _ _ = [ chart mode ]
chart Authors = pie {session, path}
chart Sources = bar {session, path}
chart Institutes = tree {session, path: path2}
......
......@@ -340,15 +340,24 @@ nodePath :: NodePath -> String
nodePath (NodePath s t i) = nodeTypePath t <> "/" <> show s <> id
where id = maybe "" (\j -> "/" <> show j) i
data ChartType = Histo | Scatter | ChartPie | ChartTree
data ChartType = Histo | Scatter | ChartPie | ChartBar | ChartTree
instance showChartType :: Show ChartType
where
show Histo = "chart"
show Scatter = "scatter"
show ChartBar = "bar"
show ChartPie = "pie"
show ChartTree = "tree"
chartTypeFromString :: String -> Maybe ChartType
chartTypeFromString "bar" = Just ChartBar
chartTypeFromString "chart" = Just Histo
chartTypeFromString "pie" = Just ChartPie
chartTypeFromString "scatter" = Just Scatter
chartTypeFromString "tree" = Just ChartTree
chartTypeFromString _ = Nothing
type Id = Int
type Limit = Int
type Offset = Int
......
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