Commit 368428a1 authored by Karen Konou's avatar Karen Konou

[Charts] fix after merge

parent f7cd32be
Pipeline #3395 failed with stage
module Gargantext.Components.Charts.Options.ECharts where module Gargantext.Components.Charts.Options.ECharts where
import Prelude
import CSS.Common (normal) import CSS.Common (normal)
import CSS.FontStyle (FontStyle(..)) import CSS.FontStyle (FontStyle(..))
import Data.Maybe (Maybe(..)) import Data.Maybe (Maybe(..))
...@@ -11,9 +13,8 @@ import Gargantext.Components.Charts.Options.Font (IconOptions(..), Shape(..), Te ...@@ -11,9 +13,8 @@ import Gargantext.Components.Charts.Options.Font (IconOptions(..), Shape(..), Te
import Gargantext.Components.Charts.Options.Legend (legendType, LegendMode(..), PlainOrScroll(..), selectedMode, Orientation(..), orient) import Gargantext.Components.Charts.Options.Legend (legendType, LegendMode(..), PlainOrScroll(..), selectedMode, Orientation(..), orient)
import Gargantext.Components.Charts.Options.Position (Align(..), LeftRelativePosition(..), TopRelativePosition(..), numberPosition, percentPosition, relativePosition) import Gargantext.Components.Charts.Options.Position (Align(..), LeftRelativePosition(..), TopRelativePosition(..), numberPosition, percentPosition, relativePosition)
import Gargantext.Components.Charts.Options.Series (Series, seriesPieD1) import Gargantext.Components.Charts.Options.Series (Series, seriesPieD1)
import Gargantext.Components.Charts.Options.Type (DataZoom, EChartRef, EChartsInstance, Echarts, Legend, MouseEvent, Option, Title, XAxis, YAxis, xAxis, yAxis) import Gargantext.Components.Charts.Options.Type (DataZoom, EChartRef, EChartsInstance, Echarts, Legend, MouseEvent, Option, Title, XAxis, YAxis, LegendSelectChangedEvent, xAxis, yAxis)
import Gargantext.Utils.Reactix as R2 import Gargantext.Utils.Reactix as R2
import Prelude
import React (ReactClass, unsafeCreateElementDynamic) import React (ReactClass, unsafeCreateElementDynamic)
import Reactix as R import Reactix as R
import Record.Extra as RX import Record.Extra as RX
...@@ -185,7 +186,7 @@ data Options = Options ...@@ -185,7 +186,7 @@ data Options = Options
, addZoom :: Boolean , addZoom :: Boolean
, tooltip :: Tooltip , tooltip :: Tooltip
, onClick :: Maybe (MouseEvent -> Effect Unit) , onClick :: Maybe (MouseEvent -> Effect Unit)
, onLegendChanged :: Maybe (MouseEvent -> Effect Unit) , onLegendChanged :: Maybe (LegendSelectChangedEvent -> Effect Unit)
-- (?) `onInit` custom listener -- (?) `onInit` custom listener
-- --
-- * in addition of the already existing `onReady` native listener -- * in addition of the already existing `onReady` native listener
......
...@@ -47,7 +47,7 @@ derive newtype instance JSON.WriteForeign HistoMetrics ...@@ -47,7 +47,7 @@ derive newtype instance JSON.WriteForeign HistoMetrics
type Loaded = HistoMetrics type Loaded = HistoMetrics
chartOptions :: Record MetricsProps -> HistoMetrics -> Options chartOptions :: Record MetricsProps -> HistoMetrics -> Options
chartOptions { onClick, onInit } (HistoMetrics { dates: dates', count: count'}) = Options chartOptions { onClick, onLegendChanged, onInit } (HistoMetrics { dates: dates', count: count'}) = Options
{ mainTitle : "Histogram" { mainTitle : "Histogram"
, subTitle : "Distribution of publications over time" , subTitle : "Distribution of publications over time"
, xAxis : xAxis' dates' , xAxis : xAxis' dates'
...@@ -56,6 +56,7 @@ chartOptions { onClick, onInit } (HistoMetrics { dates: dates', count: count'}) ...@@ -56,6 +56,7 @@ chartOptions { onClick, onInit } (HistoMetrics { dates: dates', count: count'})
, tooltip : mkTooltip { formatter: templateFormatter "{b0}" } , tooltip : mkTooltip { formatter: templateFormatter "{b0}" }
, series , series
, onClick , onClick
, onLegendChanged
, onInit , onInit
} }
where where
...@@ -95,7 +96,7 @@ histo props = R.createElement histoCpt props [] ...@@ -95,7 +96,7 @@ histo props = R.createElement histoCpt props []
histoCpt :: R.Component Props histoCpt :: R.Component Props
histoCpt = here.component "histo" cpt histoCpt = here.component "histo" cpt
where where
cpt { boxes, path, session, onClick, onInit } _ = do cpt { boxes, path, session, onClick, onLegendChanged, onInit } _ = do
reload <- T.useBox T2.newReload reload <- T.useBox T2.newReload
pure $ metricsWithCacheLoadView pure $ metricsWithCacheLoadView
...@@ -108,6 +109,7 @@ histoCpt = here.component "histo" cpt ...@@ -108,6 +109,7 @@ histoCpt = here.component "histo" cpt
, reload , reload
, session , session
, onClick , onClick
, onLegendChanged
, onInit , onInit
} }
......
...@@ -55,7 +55,7 @@ derive newtype instance JSON.ReadForeign Metrics ...@@ -55,7 +55,7 @@ derive newtype instance JSON.ReadForeign Metrics
type Loaded = Array Metric type Loaded = Array Metric
scatterOptions :: Record MetricsProps -> Array Metric -> Options scatterOptions :: Record MetricsProps -> Array Metric -> Options
scatterOptions { onClick, onInit } metrics' = Options scatterOptions { onClick, onLegendChanged, onInit } metrics' = Options
{ mainTitle : "Ngrams Selection Metrics" { mainTitle : "Ngrams Selection Metrics"
, subTitle : "Local metrics (Inc/Exc, Spe/Gen), Global metrics (TFICF maillage)" , subTitle : "Local metrics (Inc/Exc, Spe/Gen), Global metrics (TFICF maillage)"
, xAxis : xAxis { min: -1 } , xAxis : xAxis { min: -1 }
...@@ -64,6 +64,7 @@ scatterOptions { onClick, onInit } metrics' = Options ...@@ -64,6 +64,7 @@ scatterOptions { onClick, onInit } metrics' = Options
, addZoom : false , addZoom : false
, tooltip : mkTooltip { formatter: templateFormatter "{b0}" } , tooltip : mkTooltip { formatter: templateFormatter "{b0}" }
, onClick , onClick
, onLegendChanged
, onInit , onInit
} }
where where
...@@ -108,7 +109,7 @@ metrics props = R.createElement metricsCpt props [] ...@@ -108,7 +109,7 @@ metrics props = R.createElement metricsCpt props []
metricsCpt :: R.Component Props metricsCpt :: R.Component Props
metricsCpt = here.component "etrics" cpt metricsCpt = here.component "etrics" cpt
where where
cpt { boxes, onClick, onInit, path, session } _ = do cpt { boxes, onClick, onLegendChanged, onInit, path, session } _ = do
reload <- T.useBox T2.newReload reload <- T.useBox T2.newReload
pure $ metricsWithCacheLoadView { pure $ metricsWithCacheLoadView {
...@@ -121,6 +122,7 @@ metricsCpt = here.component "etrics" cpt ...@@ -121,6 +122,7 @@ metricsCpt = here.component "etrics" cpt
, reload , reload
, session , session
, onClick , onClick
, onLegendChanged
, onInit , onInit
} }
......
...@@ -53,7 +53,7 @@ derive newtype instance JSON.WriteForeign HistoMetrics ...@@ -53,7 +53,7 @@ derive newtype instance JSON.WriteForeign HistoMetrics
type Loaded = HistoMetrics type Loaded = HistoMetrics
chartOptionsBar :: Record MetricsProps -> HistoMetrics -> Options chartOptionsBar :: Record MetricsProps -> HistoMetrics -> Options
chartOptionsBar { onClick, onInit } (HistoMetrics { dates: dates', count: count'}) = Options chartOptionsBar { onClick, onLegendChanged, onInit } (HistoMetrics { dates: dates', count: count'}) = Options
{ mainTitle : "Bar" { mainTitle : "Bar"
, subTitle : "Count of MapTerm" , subTitle : "Count of MapTerm"
, xAxis : xAxis' $ map (\t -> joinWith " " $ map (take 3) $ A.take 3 $ filter (\s -> length s > 3) $ split (Pattern " ") t) dates' , xAxis : xAxis' $ map (\t -> joinWith " " $ map (take 3) $ A.take 3 $ filter (\s -> length s > 3) $ split (Pattern " ") t) dates'
...@@ -62,11 +62,12 @@ chartOptionsBar { onClick, onInit } (HistoMetrics { dates: dates', count: count' ...@@ -62,11 +62,12 @@ chartOptionsBar { onClick, onInit } (HistoMetrics { dates: dates', count: count'
, addZoom : false , addZoom : false
, tooltip : mkTooltip { formatter: templateFormatter "{b0}" } , tooltip : mkTooltip { formatter: templateFormatter "{b0}" }
, onClick , onClick
, onLegendChanged
, onInit , onInit
} }
chartOptionsPie :: Record MetricsProps -> HistoMetrics -> Options chartOptionsPie :: Record MetricsProps -> HistoMetrics -> Options
chartOptionsPie { onClick, onInit } (HistoMetrics { dates: dates', count: count'}) = Options chartOptionsPie { onClick, onLegendChanged, onInit } (HistoMetrics { dates: dates', count: count'}) = Options
{ mainTitle : "Pie" { mainTitle : "Pie"
, subTitle : "Distribution by MapTerm" , subTitle : "Distribution by MapTerm"
, xAxis : xAxis' [] , xAxis : xAxis' []
...@@ -76,6 +77,7 @@ chartOptionsPie { onClick, onInit } (HistoMetrics { dates: dates', count: count' ...@@ -76,6 +77,7 @@ chartOptionsPie { onClick, onInit } (HistoMetrics { dates: dates', count: count'
, addZoom : false , addZoom : false
, tooltip : mkTooltip { formatter: templateFormatter "{b0}" } , tooltip : mkTooltip { formatter: templateFormatter "{b0}" }
, onClick , onClick
, onLegendChanged
, onInit , onInit
} }
...@@ -101,7 +103,7 @@ pie = R2.leafComponent pieCpt ...@@ -101,7 +103,7 @@ pie = R2.leafComponent pieCpt
pieCpt :: R.Component Props pieCpt :: R.Component Props
pieCpt = here.component "pie" cpt pieCpt = here.component "pie" cpt
where where
cpt { boxes, path, session, onClick, onInit } _ = do cpt { boxes, path, session, onClick, onLegendChanged, onInit } _ = do
reload <- T.useBox T2.newReload reload <- T.useBox T2.newReload
pure $ metricsWithCacheLoadView pure $ metricsWithCacheLoadView
...@@ -114,6 +116,7 @@ pieCpt = here.component "pie" cpt ...@@ -114,6 +116,7 @@ pieCpt = here.component "pie" cpt
, reload , reload
, session , session
, onClick , onClick
, onLegendChanged
, onInit , onInit
} }
...@@ -131,7 +134,7 @@ bar props = R.createElement barCpt props [] ...@@ -131,7 +134,7 @@ bar props = R.createElement barCpt props []
barCpt :: R.Component Props barCpt :: R.Component Props
barCpt = here.component "bar" cpt barCpt = here.component "bar" cpt
where where
cpt { boxes, path, session, onClick, onInit} _ = do cpt { boxes, path, session, onClick, onLegendChanged, onInit} _ = do
reload <- T.useBox T2.newReload reload <- T.useBox T2.newReload
pure $ metricsWithCacheLoadView { pure $ metricsWithCacheLoadView {
...@@ -144,6 +147,7 @@ barCpt = here.component "bar" cpt ...@@ -144,6 +147,7 @@ barCpt = here.component "bar" cpt
, reload , reload
, session , session
, onClick , onClick
, onLegendChanged
, onInit , onInit
} }
......
...@@ -8,7 +8,7 @@ import Data.Ord.Generic (genericCompare) ...@@ -8,7 +8,7 @@ import Data.Ord.Generic (genericCompare)
import Data.Show.Generic (genericShow) import Data.Show.Generic (genericShow)
import Effect (Effect) import Effect (Effect)
import Gargantext.Components.App.Store (Boxes) import Gargantext.Components.App.Store (Boxes)
import Gargantext.Components.Charts.Options.Type (EChartsInstance, MouseEvent) import Gargantext.Components.Charts.Options.Type (EChartsInstance, MouseEvent, LegendSelectChangedEvent)
import Gargantext.Components.Nodes.Corpus.Chart.Histo (histo) import Gargantext.Components.Nodes.Corpus.Chart.Histo (histo)
import Gargantext.Components.Nodes.Corpus.Chart.Metrics (metrics) import Gargantext.Components.Nodes.Corpus.Chart.Metrics (metrics)
import Gargantext.Components.Nodes.Corpus.Chart.Pie (bar, pie) import Gargantext.Components.Nodes.Corpus.Chart.Pie (bar, pie)
...@@ -55,51 +55,52 @@ allPredefinedCharts = ...@@ -55,51 +55,52 @@ allPredefinedCharts =
type Params = type Params =
( boxes :: Boxes ( boxes :: Boxes
, corpusId :: NodeID , corpusId :: NodeID
-- optinal params -- optinal params
, limit :: Maybe Int , limit :: Maybe Int
, listId :: Maybe Int , listId :: Maybe Int
, onClick :: Maybe (MouseEvent -> Effect Unit) , onClick :: Maybe (MouseEvent -> Effect Unit)
, onInit :: Maybe (EChartsInstance -> Effect Unit) , onLegendChanged :: Maybe (LegendSelectChangedEvent -> Effect Unit)
, session :: Session , onInit :: Maybe (EChartsInstance -> Effect Unit)
, session :: Session
) )
render :: PredefinedChart -> Record Params -> R.Element render :: PredefinedChart -> Record Params -> R.Element
render CDocsHistogram { boxes, corpusId, listId, session, onClick, onInit } = render CDocsHistogram { boxes, corpusId, listId, session, onClick, onLegendChanged, onInit } =
histo { boxes, path, session, onClick, onInit } histo { boxes, path, session, onClick, onLegendChanged, onInit }
where where
path = { corpusId path = { corpusId
, listId: fromMaybe 0 listId , listId: fromMaybe 0 listId
, limit: Nothing , limit: Nothing
, tabType: TabCorpus TabDocs , tabType: TabCorpus TabDocs
} }
render CAuthorsPie { boxes, corpusId, listId, session, onClick, onInit } = render CAuthorsPie { boxes, corpusId, listId, session, onClick, onLegendChanged, onInit } =
pie { boxes, path, session, onClick, onInit } pie { boxes, path, session, onClick, onLegendChanged, onInit }
where where
path = { corpusId path = { corpusId
, listId: fromMaybe 0 listId , listId: fromMaybe 0 listId
, limit: Nothing , limit: Nothing
, tabType: TabCorpus (TabNgramType $ modeTabType Authors) , tabType: TabCorpus (TabNgramType $ modeTabType Authors)
} }
render CInstitutesTree { boxes, corpusId, limit, listId, session, onClick, onInit } = render CInstitutesTree { boxes, corpusId, limit, listId, session, onClick, onLegendChanged, onInit } =
tree { boxes, path, session, onClick, onInit } tree { boxes, path, session, onClick, onLegendChanged, onInit }
where where
path = { corpusId path = { corpusId
, limit , limit
, listId: fromMaybe 0 listId , listId: fromMaybe 0 listId
, tabType: TabCorpus (TabNgramType $ modeTabType Institutes) , tabType: TabCorpus (TabNgramType $ modeTabType Institutes)
} }
render CTermsMetrics { boxes, corpusId, limit, listId, session, onClick, onInit } = render CTermsMetrics { boxes, corpusId, limit, listId, session, onClick, onLegendChanged, onInit } =
metrics { boxes, path, session, onClick, onInit } metrics { boxes, path, session, onClick, onLegendChanged, onInit }
where where
path = { corpusId path = { corpusId
, limit , limit
, listId: fromMaybe 0 listId , listId: fromMaybe 0 listId
, tabType: TabCorpus (TabNgramType $ modeTabType Terms) , tabType: TabCorpus (TabNgramType $ modeTabType Terms)
} }
render CSourcesBar { boxes, corpusId, limit, listId, session, onClick, onInit } = render CSourcesBar { boxes, corpusId, limit, listId, session, onClick, onLegendChanged, onInit } =
bar { boxes, path, session, onClick, onInit } bar { boxes, path, session, onClick, onLegendChanged, onInit }
where where
path = { corpusId path = { corpusId
, limit , limit
......
module Gargantext.Components.Nodes.Corpus.Chart.Tree where module Gargantext.Components.Nodes.Corpus.Chart.Tree
( Loaded
, Metrics(..)
, chartUrl
, getMetricsHash
, handleResponse
, here
, loaded
, mkRequest
, tree
, treeCpt
)
where
import Gargantext.Prelude import Gargantext.Prelude
...@@ -38,7 +50,7 @@ derive newtype instance JSON.WriteForeign Metrics ...@@ -38,7 +50,7 @@ derive newtype instance JSON.WriteForeign Metrics
type Loaded = Array TreeNode type Loaded = Array TreeNode
scatterOptions :: Record MetricsProps -> Array TreeNode -> Options scatterOptions :: Record MetricsProps -> Array TreeNode -> Options
scatterOptions { onClick, onInit } nodes = Options scatterOptions { onClick, onLegendChanged, onInit } nodes = Options
{ mainTitle : "Tree" { mainTitle : "Tree"
, subTitle : "Tree Sub Title" , subTitle : "Tree Sub Title"
, xAxis : xAxis' [] , xAxis : xAxis' []
...@@ -46,6 +58,7 @@ scatterOptions { onClick, onInit } nodes = Options ...@@ -46,6 +58,7 @@ scatterOptions { onClick, onInit } nodes = Options
, series : [ mkTree TreeMap nodes] , series : [ mkTree TreeMap nodes]
, addZoom : false , addZoom : false
, tooltip : mkTooltip { formatter: templateFormatter "{b0}" } , tooltip : mkTooltip { formatter: templateFormatter "{b0}" }
, onLegendChanged
, onClick , onClick
, onInit , onInit
-- TODO improve the formatter: -- TODO improve the formatter:
...@@ -75,7 +88,7 @@ tree props = R.createElement treeCpt props [] ...@@ -75,7 +88,7 @@ tree props = R.createElement treeCpt props []
treeCpt :: R.Component Props treeCpt :: R.Component Props
treeCpt = here.component "tree" cpt treeCpt = here.component "tree" cpt
where where
cpt { boxes, path, session, onClick, onInit } _ = do cpt { boxes, path, session, onClick, onLegendChanged, onInit } _ = do
reload <- T.useBox T2.newReload reload <- T.useBox T2.newReload
pure $ metricsWithCacheLoadView pure $ metricsWithCacheLoadView
...@@ -88,6 +101,7 @@ treeCpt = here.component "tree" cpt ...@@ -88,6 +101,7 @@ treeCpt = here.component "tree" cpt
, reload , reload
, session , session
, onClick , onClick
, onLegendChanged
, onInit , onInit
} }
......
...@@ -264,6 +264,7 @@ renderChartCpt = here.component "renderChart" cpt ...@@ -264,6 +264,7 @@ renderChartCpt = here.component "renderChart" cpt
, limit: Just 1000 , limit: Just 1000
, listId: Just defaultListId , listId: Just defaultListId
, onClick: Nothing , onClick: Nothing
, onLegendChanged: Nothing
, onInit: Nothing , onInit: Nothing
, session , session
} }
......
...@@ -226,10 +226,10 @@ ngramsViewCpt' = here.component "ngramsView_clone" cpt where ...@@ -226,10 +226,10 @@ ngramsViewCpt' = here.component "ngramsView_clone" cpt where
] ]
charts params' _ = [ chart params' mode ] charts params' _ = [ chart params' mode ]
chart path Authors = pie { boxes, path, session, onClick: Nothing, onInit: Nothing } chart path Authors = pie { boxes, path, session, onClick: Nothing, onLegendChanged: Nothing, onInit: Nothing }
chart path Institutes = tree { boxes, path, session, onClick: Nothing, onInit: Nothing } chart path Institutes = tree { boxes, path, session, onClick: Nothing, onLegendChanged: Nothing, onInit: Nothing }
chart path Sources = bar { boxes, path, session, onClick: Nothing, onInit: Nothing } chart path Sources = bar { boxes, path, session, onClick: Nothing, onLegendChanged: Nothing, onInit: Nothing }
chart path Terms = metrics { boxes, path, session, onClick: Nothing, onInit: Nothing } chart path Terms = metrics { boxes, path, session, onClick: Nothing, onLegendChanged: Nothing, onInit: Nothing }
tabType = TabCorpus (TabNgramType tabNgramType) tabType = TabCorpus (TabNgramType tabNgramType)
......
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