Commit 5507abf5 authored by Alexandre Delanoë's avatar Alexandre Delanoë

[Charts] Types of Series for heteregenous list of Series type.

parent 246ab19a
...@@ -2,6 +2,7 @@ module Gargantext.Components.Charts.Charts where ...@@ -2,6 +2,7 @@ module Gargantext.Components.Charts.Charts where
import Prelude hiding (min) import Prelude hiding (min)
import Gargantext.Components.Charts.Options.Series (Series(..), D1, seriesType, SeriesShape(..))
import CSS (Color, white) import CSS (Color, white)
import Data.Maybe (Maybe(..)) import Data.Maybe (Maybe(..))
import React as R import React as R
...@@ -161,11 +162,12 @@ type AxisLabel = ...@@ -161,11 +162,12 @@ type AxisLabel =
} }
type Series = --type Series =
{ name :: String -- { name :: String
, "type" :: String -- , "type" :: String
, "data" :: Array Int -- , "data" :: Array Int
} -- }
type Title = type Title =
{ text :: String { text :: String
...@@ -436,12 +438,12 @@ tooltip' = ...@@ -436,12 +438,12 @@ tooltip' =
} }
series' :: Series series' :: D1
series' = series' =
{ {
name: "All" name: "All"
, "type": "bar" , "type": seriesType Bar
, "data": [201, 777, 879] , "data": [201.0, 777, 879]
} }
opt :: Option opt :: Option
...@@ -453,7 +455,7 @@ opt = ...@@ -453,7 +455,7 @@ opt =
,grid: {containLabel: true} ,grid: {containLabel: true}
,xAxis: xAxis' ,xAxis: xAxis'
,yAxis: yData1 ,yAxis: yData1
,series: [series'] ,series: [SeriesD1 series']
,dataZoom: [dz1', dz1', dz2', dz2'] ,dataZoom: [dz1', dz1', dz2', dz2']
} }
...@@ -591,5 +593,4 @@ sd2 = unsafeFromPropsArray ...@@ -591,5 +593,4 @@ sd2 = unsafeFromPropsArray
] ]
p'' :: R.ReactElement
p'' = p [] []
...@@ -17,3 +17,4 @@ type DataS = ...@@ -17,3 +17,4 @@ type DataS =
{ name :: String { name :: String
, value :: Number , value :: Number
} }
...@@ -11,7 +11,7 @@ import Gargantext.Components.Charts.Options.Data (DataN, DataS, DataV) ...@@ -11,7 +11,7 @@ import Gargantext.Components.Charts.Options.Data (DataN, DataS, DataV)
import Gargantext.Components.Charts.Options.Font (IconOptions(..), Shape(..), TextStyle, chartFontStyle, chartFontWeight, icon) import Gargantext.Components.Charts.Options.Font (IconOptions(..), Shape(..), TextStyle, chartFontStyle, chartFontWeight, icon)
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, SeriesName, SeriesShape(..), seriesType) import Gargantext.Components.Charts.Options.Series (Series(..), SeriesName, SeriesShape(..), seriesType, D1, D2)
import Gargantext.Components.Charts.Options.Type (DataZoom, Echarts, Legend, Option, Title, Tooltip, XAxis, YAxis) import Gargantext.Components.Charts.Options.Type (DataZoom, Echarts, Legend, Option, Title, Tooltip, XAxis, YAxis)
import React (unsafeCreateElementDynamic) import React (unsafeCreateElementDynamic)
import React as R import React as R
...@@ -24,20 +24,20 @@ chart :: Options -> R.ReactElement ...@@ -24,20 +24,20 @@ chart :: Options -> R.ReactElement
chart = echarts <<< chartWith <<< opts chart = echarts <<< chartWith <<< opts
chartWith :: Option -> Echarts chartWith :: Option -> Echarts
chartWith opts = { className: Nothing chartWith opts = { className : Nothing
, style: Nothing , style : Nothing
, theme: Nothing , theme : Nothing
, group: Nothing , group : Nothing
, option: opts , option : opts
, initOpts: Nothing , initOpts : Nothing
, notMerge: Nothing , notMerge : Nothing
, lazyUpdate: Nothing , lazyUpdate: Nothing
, loading: Nothing , loading : Nothing
, optsLoading: Nothing , optsLoading: Nothing
, onReady: Nothing , onReady : Nothing
, resizable: Nothing , resizable : Nothing
, onEvents: Nothing , onEvents : Nothing
} }
echarts :: Echarts -> R.ReactElement echarts :: Echarts -> R.ReactElement
echarts chart = unsafeCreateElementDynamic (unsafeCoerce eChartsClass) chart [] echarts chart = unsafeCreateElementDynamic (unsafeCoerce eChartsClass) chart []
...@@ -154,12 +154,20 @@ tooltip' = ...@@ -154,12 +154,20 @@ tooltip' =
} }
series :: SeriesShape -> SeriesName -> Array DataS -> Series series :: SeriesShape -> SeriesName -> Array DataS -> D1
series sh name ss = { name: name series sh name ss = { name: name
, "type": seriesType sh , "type": seriesType sh
, "data": ss , "data": ss
} }
seriesD2 :: SeriesShape -> Number -> Array (Array Number) -> D2
seriesD2 sh size ds = { "symbolSize" : size
, "data" : ds
, "type" : seriesType sh
}
data YAxisFormat = YAxisFormat { position :: String data YAxisFormat = YAxisFormat { position :: String
, visible :: Boolean , visible :: Boolean
} }
...@@ -196,7 +204,7 @@ opts (Options { mainTitle : mainTitle ...@@ -196,7 +204,7 @@ opts (Options { mainTitle : mainTitle
, axisLabel: {formatter: "{value}"} , axisLabel: {formatter: "{value}"}
, show: visible , show: visible
} }
,dataZoom: if addZoom then [zoom Slider, zoom Inside] else [] , dataZoom: if addZoom then [zoom Slider, zoom Inside] else []
, children : unsafeCoerce [] , children : unsafeCoerce []
} }
...@@ -217,10 +225,10 @@ zoom z = { ...@@ -217,10 +225,10 @@ zoom z = {
} }
seriesPie :: Series seriesPie :: D1
seriesPie = seriesPie =
{ {
name: "Pie" name: "Pie name"
, "type": seriesType Pie , "type": seriesType Pie
, "data": [{name: "t1", value: 50.0}, , "data": [{name: "t1", value: 50.0},
{name: "t2", value: 45.0}, {name: "t2", value: 45.0},
...@@ -231,7 +239,6 @@ seriesPie = ...@@ -231,7 +239,6 @@ seriesPie =
} }
textStyle2 :: TextStyle textStyle2 :: TextStyle
textStyle2 = textStyle2 =
{ {
......
...@@ -4,7 +4,6 @@ import Prelude ...@@ -4,7 +4,6 @@ import Prelude
import Gargantext.Components.Charts.Options.Data (DataS) import Gargantext.Components.Charts.Options.Data (DataS)
newtype SeriesType = SeriesType String newtype SeriesType = SeriesType String
type SeriesName = String type SeriesName = String
...@@ -12,7 +11,7 @@ type SeriesName = String ...@@ -12,7 +11,7 @@ type SeriesName = String
data SeriesShape = Line data SeriesShape = Line
| Bar | PictorialBar | Bar | PictorialBar
| Pie | Pie
| Scatter | EffectScater | Scatter | EffectScatter
| Radar | Radar
| Tree | TreeMap | Tree | TreeMap
| Sunburst | Sunburst
...@@ -35,13 +34,24 @@ instance showSeriesShape :: Show SeriesShape where ...@@ -35,13 +34,24 @@ instance showSeriesShape :: Show SeriesShape where
show Sunburst = "sunburst" show Sunburst = "sunburst"
show Funnel = "funnel" show Funnel = "funnel"
show Heatmap = "heatmap" show Heatmap = "heatmap"
show EffectScatter = "effectScatter" -- ^ https://ecomfe.github.io/echarts-examples/public/editor.html?c=scatter-effect
show Scatter = "scatter" -- ^ https://ecomfe.github.io/echarts-examples/public/editor.html?c=scatter-simple
show _ = "" show _ = ""
seriesType :: SeriesShape -> SeriesType seriesType :: SeriesShape -> SeriesType
seriesType = SeriesType <<< show seriesType = SeriesType <<< show
type Series =
data Series = SeriesD1 D1 | SeriesD2 D2
type D1 =
{ name :: String { name :: String
, "type" :: SeriesType
, "data" :: Array DataS , "data" :: Array DataS
, "type" :: SeriesType
} }
type D2 =
{ "symbolSize" :: Number
, "data" :: Array (Array Number)
, "type" :: SeriesType
}
...@@ -14,19 +14,19 @@ import React as R ...@@ -14,19 +14,19 @@ import React as R
newtype ChartAlign = ChartAlign String newtype ChartAlign = ChartAlign String
type Echarts = type Echarts =
{ className :: Maybe String, { className :: Maybe String
style :: Maybe String, -- objealect-black-altdarkmincnaquadahherry-blossomect, , style :: Maybe String -- objealect-black-altdarkmincnaquadahherry-blossomect,
theme :: Maybe String, , theme :: Maybe String
group :: Maybe String, , group :: Maybe String
option :: Option, -- PropTypes.object.isRequired, , option :: Option -- PropTypes.object.isRequired,
initOpts :: Maybe String, -- PropTypes.object, , initOpts :: Maybe String -- PropTypes.object,
notMerge :: Maybe Boolean, , notMerge :: Maybe Boolean
lazyUpdate :: Maybe Boolean, , lazyUpdate :: Maybe Boolean
loading :: Maybe Boolean, , loading :: Maybe Boolean
optsLoading :: Maybe OptsLoading, -- PropTypes.object, , optsLoading :: Maybe OptsLoading -- PropTypes.object,
onReady :: Maybe String, -- PropTypes.func, , onReady :: Maybe String -- PropTypes.func,
resizable :: Maybe Boolean, -- PropTypes.bool, , resizable :: Maybe Boolean -- PropTypes.bool,
onEvents :: Maybe String -- PropTypes.object , onEvents :: Maybe String -- PropTypes.object
} }
type Option = type Option =
...@@ -42,8 +42,7 @@ type Option = ...@@ -42,8 +42,7 @@ type Option =
} }
type Title = type Title =
{ { id :: String -- None by default
id :: String -- None by default
, show :: Boolean -- default True , show :: Boolean -- default True
, text :: String -- default '' , text :: String -- default ''
, link :: String -- default '' , link :: String -- default ''
...@@ -72,11 +71,11 @@ type Title = ...@@ -72,11 +71,11 @@ type Title =
} }
type OptsLoading = type OptsLoading =
{ text :: String, { text :: String
color :: Color, --- color , color :: Color --- color
textColor :: Color, --color , textColor :: Color --color
maskColor :: Color, --color , maskColor :: Color --color
zlevel :: Int , zlevel :: Int
} }
type DataZoom = type DataZoom =
......
...@@ -6,6 +6,7 @@ import Data.Array (zip) ...@@ -6,6 +6,7 @@ import Data.Array (zip)
import Data.Tuple (Tuple(..)) import Data.Tuple (Tuple(..))
import Gargantext.Components.Charts.Options.ECharts import Gargantext.Components.Charts.Options.ECharts
import Gargantext.Components.Charts.Options.Series import Gargantext.Components.Charts.Options.Series
import Gargantext.Components.Charts.Options.Type (Option)
import Data.Unit (Unit) import Data.Unit (Unit)
import Data.Int (toNumber) import Data.Int (toNumber)
import React.DOM (div, h1, text, title) import React.DOM (div, h1, text, title)
...@@ -32,6 +33,7 @@ render dispatch _ state _ = [ ...@@ -32,6 +33,7 @@ render dispatch _ state _ = [
, div [className "row"] (map (\school -> div [className "col-md-4 content"] [chart $ focus school]) , div [className "row"] (map (\school -> div [className "col-md-4 content"] [chart $ focus school])
[ "Télécom Bretagne", "Mines Nantes", "Eurecom"] [ "Télécom Bretagne", "Mines Nantes", "Eurecom"]
) )
--, chart scatterEx
] ]
where where
...@@ -39,7 +41,7 @@ render dispatch _ state _ = [ ...@@ -39,7 +41,7 @@ render dispatch _ state _ = [
focus school = Options { mainTitle : ("Focus " <> school) focus school = Options { mainTitle : ("Focus " <> school)
, subTitle : "Total scientific publications" , subTitle : "Total scientific publications"
, xAxis : xAxis ["2015", "2016", "2017"] , xAxis : xAxis ["2015", "2016", "2017"]
, yAxis : [series Bar "Bar Data" [ {name: "val1", value: 50.0} , yAxis : [SeriesD1 $ series Bar "Bar Data" [ {name: "val1", value: 50.0}
, {name: "val2", value: 70.0} , {name: "val2", value: 70.0}
, {name: "val3", value: 80.0} , {name: "val3", value: 80.0}
] ]
...@@ -63,7 +65,7 @@ naturePublis :: Options ...@@ -63,7 +65,7 @@ naturePublis :: Options
naturePublis = Options { mainTitle : "Nature of publications" naturePublis = Options { mainTitle : "Nature of publications"
, subTitle : "Distribution by type" , subTitle : "Distribution by type"
, xAxis : xAxis [] , xAxis : xAxis []
, yAxis : [series Funnel "Funnel Data" naturePublis_y] , yAxis : [SeriesD1 $ series Funnel "Funnel Data" naturePublis_y]
, yAxisFormat : (YAxisFormat { position : "left" , yAxisFormat : (YAxisFormat { position : "left"
, visible : false , visible : false
}) })
...@@ -80,7 +82,7 @@ globalPublis :: Options ...@@ -80,7 +82,7 @@ globalPublis :: Options
globalPublis = (Options { mainTitle : "Global Scientific Publications" globalPublis = (Options { mainTitle : "Global Scientific Publications"
, subTitle : "Distribution of scientific publications by IMT's Schools over time" , subTitle : "Distribution of scientific publications by IMT's Schools over time"
, xAxis : xAxis (map show globalPublis_x) , xAxis : xAxis (map show globalPublis_x)
, yAxis : [series Bar "Number of publication of IMT / year" $ map (\n -> {name: "", value: toNumber n }) globalPublis_y] , yAxis : [SeriesD1 $ series Bar "Number of publication of IMT / year" $ map (\n -> {name: "", value: toNumber n }) globalPublis_y]
, yAxisFormat : (YAxisFormat { position : "left" , yAxisFormat : (YAxisFormat { position : "left"
, visible : true , visible : true
}) })
...@@ -96,13 +98,52 @@ distriBySchool :: Options ...@@ -96,13 +98,52 @@ distriBySchool :: Options
distriBySchool = Options { mainTitle : "School production in 2017" distriBySchool = Options { mainTitle : "School production in 2017"
, subTitle : "Distribution by school" , subTitle : "Distribution by school"
, xAxis : xAxis [] , xAxis : xAxis []
, yAxis : [ series Pie "Pie data" (map (\(Tuple n v) -> {name: n, value: toNumber v}) distriBySchool_y)] , yAxis : [ SeriesD1 $ series Pie "Pie data" (map (\(Tuple n v) -> {name: n, value: toNumber v}) distriBySchool_y)]
, yAxisFormat : (YAxisFormat { position : "" , yAxisFormat : (YAxisFormat { position : ""
, visible : false , visible : false
}) })
, addZoom : false , addZoom : false
} }
scatterEx :: Options
scatterEx = Options { mainTitle : "Scatter test"
, subTitle : "Scatter subtitle"
, xAxis : xAxis []
, yAxis : [ SeriesD2 $ seriesD2 Scatter 20.0 [[2.0,3.0],[3.0,4.0]]]
, yAxisFormat : (YAxisFormat { position : ""
, visible : false
})
, addZoom : false
}
--scatterEx :: Options
--scatterEx = { -- title: "title"
-- xAxis : {}
-- , yAxis : {}
-- , "data" : []
-- , series : [ { "symbolSize" : 20
-- , data : [[1,2]]
-- , "type" : "scatter"
-- }
-- ]
-- }
-- Option {mainTitle : "Scatter ex"
-- , subTitle : "Subtitle"
-- , xAxis : xAxis []
-- , yAxis : []
-- , yAxisFormat : (YAxisFormat { position : ""
-- , visible : false
-- })
-- --, series : [SeriesD2 20 [[2,2]] Scatter]
--
-- , addZoom : false
-- }
layoutDashboard :: forall props. Spec State props Action layoutDashboard :: forall props. Spec State props Action
layoutDashboard = simpleSpec performAction render layoutDashboard = simpleSpec performAction render
...@@ -13,14 +13,15 @@ import Effect (Effect) ...@@ -13,14 +13,15 @@ import Effect (Effect)
import Effect.Aff (Aff) import Effect.Aff (Aff)
import Effect.Class (liftEffect) import Effect.Class (liftEffect)
import Effect.Console (log) import Effect.Console (log)
import Gargantext.Components.Charts.Charts (p'')
import Gargantext.Config.REST (get) import Gargantext.Config.REST (get)
import React (ReactElement) import React (ReactElement)
import React.DOM (a, b, b', br', div, input, option, select, span, table, tbody, td, text, th, thead, tr) import React.DOM (a, b, b', br', div, input, option, select, span, table, tbody, td, text, th, thead, tr, p)
import React.DOM.Props (_type, className, href, onChange, onClick, scope, selected, value) import React.DOM.Props (_type, className, href, onChange, onClick, scope, selected, value)
import Thermite (PerformAction, Render, Spec, cotransform, defaultPerformAction, modifyState, simpleSpec) import Thermite (PerformAction, Render, Spec, cotransform, defaultPerformAction, modifyState, simpleSpec)
import Unsafe.Coerce (unsafeCoerce) import Unsafe.Coerce (unsafeCoerce)
p'' :: ReactElement
p'' = p [] []
--main :: forall e. Eff (dom:: DOM, console :: CONSOLE, ajax :: AJAX | e) Unit --main :: forall e. Eff (dom:: DOM, console :: CONSOLE, ajax :: AJAX | e) Unit
--main = do --main = do
......
module Test.Main where module Test.Main where
import Prelude --import Prelude
import Control.Monad.Eff (Eff) --import Control.Monad.Eff (Eff)
import Control.Monad.Eff.Console (CONSOLE, log) --import Control.Monad.Eff.Console (CONSOLE, log)
--
main :: forall e. Eff (console :: CONSOLE | e) Unit --main :: forall e. Eff (console :: CONSOLE | e) Unit
main = do --main = do
log "You should add some tests." -- log "You should add some tests."
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