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