[CHARTS] refactoring to fix the support of tooltips, color of scatters bubble...

parent e8342824
...@@ -8,6 +8,8 @@ module Gargantext.Components.Charts.Options.Color ...@@ -8,6 +8,8 @@ module Gargantext.Components.Charts.Options.Color
, magenta , magenta
, violet , violet
, black , black
, grey
, green
) where ) where
import Prelude import Prelude
...@@ -41,3 +43,9 @@ violet = cssColor CSS.violet ...@@ -41,3 +43,9 @@ violet = cssColor CSS.violet
black :: Color black :: Color
black = stringColor "black" black = stringColor "black"
grey :: Color
grey = stringColor "grey"
green :: Color
green = stringColor "green"
module Gargantext.Components.Charts.Options.Data where module Gargantext.Components.Charts.Options.Data where
import Gargantext.Components.Charts.Options.Font (TextStyle, Icon) import Record.Unsafe (unsafeSet)
import Unsafe.Coerce (unsafeCoerce)
import Gargantext.Types (class Optional)
import Gargantext.Components.Charts.Options.Font (TextStyle, Icon, ItemStyle)
type DataLegend = type DataLegend =
{ name :: String { name :: String
...@@ -13,8 +16,32 @@ type DataAxis = ...@@ -13,8 +16,32 @@ type DataAxis =
, textStyle :: TextStyle , textStyle :: TextStyle
} }
type DataS = type RequiredData v o =
{ name :: String { value :: v
, value :: Number | o
} }
type OptionalData =
( name :: String
, symbolSize :: Number
, itemStyle :: ItemStyle
-- ^ the style setting about single data point(bubble).
, label :: { show :: Boolean }
)
type DataSerie v = RequiredData v OptionalData
dataSerie :: forall v o. Optional o OptionalData => RequiredData v o -> DataSerie v
dataSerie = unsafeCoerce
dataSerieV :: forall v. v -> DataSerie v
dataSerieV value = dataSerie {value}
type DataD1 = DataSerie Number
type DataD2 = DataSerie (Array Number)
dataD1 :: forall o. Optional o OptionalData => Record o -> Number -> DataD1
dataD1 o x = unsafeCoerce (unsafeSet "value" x o)
dataD2 :: forall o. Optional o OptionalData => Record o -> Number -> Number -> DataD2
dataD2 o x y = unsafeCoerce (unsafeSet "value" [x,y] o)
...@@ -7,12 +7,12 @@ import CSS.Common (normal) ...@@ -7,12 +7,12 @@ import CSS.Common (normal)
import Data.Array (length) import Data.Array (length)
import Data.Maybe (Maybe(..)) import Data.Maybe (Maybe(..))
import Gargantext.Components.Charts.Options.Color (transparent, violet, black) import Gargantext.Components.Charts.Options.Color (transparent, violet, black)
import Gargantext.Components.Charts.Options.Data (DataLegend, DataS, DataAxis) import Gargantext.Components.Charts.Options.Data (DataLegend, DataAxis, dataSerie)
import Gargantext.Components.Charts.Options.Font (IconOptions(..), Shape(..), TextStyle, chartFontStyle, chartFontWeight, icon) import Gargantext.Components.Charts.Options.Font (IconOptions(..), Shape(..), TextStyle, chartFontStyle, chartFontWeight, icon, mkTooltip, Tooltip)
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, Chart(..), seriesType, seriesD1) import Gargantext.Components.Charts.Options.Series (Series, SeriesName, Chart(..), seriesPieD1)
import Gargantext.Components.Charts.Options.Type (DataZoom, Echarts, Legend, Option, Title, Tooltip, XAxis, YAxis, xAxis, yAxis) import Gargantext.Components.Charts.Options.Type (DataZoom, Echarts, Legend, Option, Title, XAxis, YAxis, xAxis, yAxis)
import React (unsafeCreateElementDynamic) import React (unsafeCreateElementDynamic)
import React as R import React as R
import Unsafe.Coerce (unsafeCoerce) import Unsafe.Coerce (unsafeCoerce)
...@@ -137,12 +137,6 @@ yAxis1 = yAxis ...@@ -137,12 +137,6 @@ yAxis1 = yAxis
, show: true , show: true
} }
tooltip' :: Tooltip
tooltip' =
{ trigger: "axis"
, formatter: Nothing
}
xAxis' :: Array String -> XAxis xAxis' :: Array String -> XAxis
xAxis' [] = unsafeCoerce {} xAxis' [] = unsafeCoerce {}
xAxis' xs = xAxis xAxis' xs = xAxis
...@@ -175,21 +169,24 @@ data Options = Options ...@@ -175,21 +169,24 @@ data Options = Options
, yAxis :: YAxis , yAxis :: YAxis
, series :: Array Series , series :: Array Series
, addZoom :: Boolean , addZoom :: Boolean
, tooltip :: Tooltip
} }
tooltipTriggerAxis :: Tooltip
tooltipTriggerAxis = mkTooltip {trigger: "axis"}
opts :: Options -> Option opts :: Options -> Option
opts (Options { mainTitle opts (Options { mainTitle
, subTitle , subTitle
, xAxis , xAxis
, yAxis , yAxis
, series , series
, tooltip
, addZoom , addZoom
}) = }) =
{ title: title mainTitle subTitle { title: title mainTitle subTitle
, legend , legend
, tooltip: { trigger: "axis" , tooltip
, formatter: Nothing
}
, grid: {containLabel: true} , grid: {containLabel: true}
, series , series
, xAxis , xAxis
...@@ -215,16 +212,14 @@ zoom z = { ...@@ -215,16 +212,14 @@ zoom z = {
seriesPie :: Series seriesPie :: Series
seriesPie = seriesD1 seriesPie = seriesPieD1
{ name: "Pie name" { name: "Pie name" }
, "type": seriesType Pie (dataSerie <$> [ {name: "t1", value: 50.0}
, "data": [{name: "t1", value: 50.0}, , {name: "t2", value: 45.0}
{name: "t2", value: 45.0}, , {name: "t3", value: 65.0}
{name: "t3", value: 65.0}, , {name: "t4", value: 15.0}
{name: "t4", value: 15.0}, , {name: "t5", value: 23.0}
{name: "t5", value: 23.0} ])
]
}
textStyle2 :: TextStyle textStyle2 :: TextStyle
......
module Gargantext.Components.Charts.Options.Font module Gargantext.Components.Charts.Options.Font
( ( ItemStyle
TextStyle, , ItemStyleOptional
ChartFontStyle(), , itemStyle
chartFontStyle, , TextStyle
ChartFontWeight(), , ChartFontStyle()
chartFontWeight, , chartFontStyle
Icon(), , ChartFontWeight()
ImageURL(..), , chartFontWeight
Shape(..), , Icon()
IconOptions(..), , ImageURL(..)
icon , Shape(..)
, IconOptions(..)
, icon
, Formatter
, templateFormatter
, Tooltip
, TooltipOptional
, mkTooltip
) where ) where
import Prelude (Unit, ($), (<<<), (<>)) import Prelude (Unit, ($), (<<<), (<>))
...@@ -20,6 +27,8 @@ import CSS (FontStyle(..), FontWeight(..), Prefixed(..), Value(..)) ...@@ -20,6 +27,8 @@ import CSS (FontStyle(..), FontWeight(..), Prefixed(..), Value(..))
import Data.String (toLower) import Data.String (toLower)
import Gargantext.Components.Charts.Options.Color (Color) import Gargantext.Components.Charts.Options.Color (Color)
import Gargantext.Components.Charts.Options.Position (LeftRelativePosition, Position, TopRelativePosition) import Gargantext.Components.Charts.Options.Position (LeftRelativePosition, Position, TopRelativePosition)
import Gargantext.Types (class Optional)
import Unsafe.Coerce (unsafeCoerce)
type TextStyle = type TextStyle =
...@@ -71,3 +80,34 @@ data IconOptions = Shape Shape | Image ImageURL ...@@ -71,3 +80,34 @@ data IconOptions = Shape Shape | Image ImageURL
icon :: IconOptions -> Icon icon :: IconOptions -> Icon
icon (Shape s) = Icon <<< toLower $ genericShow s icon (Shape s) = Icon <<< toLower $ genericShow s
icon (Image (ImageURL url)) = Icon $ "image://" <> url icon (Image (ImageURL url)) = Icon $ "image://" <> url
data ItemStyle
type ItemStyleOptional =
( color :: Color
)
itemStyle :: forall o. Optional o ItemStyleOptional => Record o -> ItemStyle
itemStyle = unsafeCoerce
data Formatter
templateFormatter :: String -> Formatter
templateFormatter = unsafeCoerce
-- TODO callbackFormatter :: (...) -> Formatter
data Tooltip
type TooltipOptional =
( trigger :: String
-- ^ Not all tooltips support triggers.
-- Grid and legend tooltips : yes
-- Series : no
, show :: Boolean
, formatter :: Formatter
)
mkTooltip :: forall o. Optional o TooltipOptional => Record o -> Tooltip
mkTooltip = unsafeCoerce
module Gargantext.Components.Charts.Options.Series where module Gargantext.Components.Charts.Options.Series where
import Record.Unsafe (unsafeSet)
import Unsafe.Coerce (unsafeCoerce) import Unsafe.Coerce (unsafeCoerce)
import Prelude import Prelude
import Gargantext.Types (class Optional) import Gargantext.Types (class Optional)
import Gargantext.Components.Charts.Options.Color (Color) import Gargantext.Components.Charts.Options.Font (ItemStyle, Tooltip)
import Gargantext.Components.Charts.Options.Data (DataS) import Gargantext.Components.Charts.Options.Data (DataD1, DataD2)
data ItemStyle
type ItemStyleOptional =
( color :: Color
)
itemStyle :: forall o. Optional o ItemStyleOptional => Record o -> ItemStyle
itemStyle = unsafeCoerce
newtype SeriesType = SeriesType String newtype SeriesType = SeriesType String
...@@ -58,54 +49,53 @@ seriesType :: Chart -> SeriesType ...@@ -58,54 +49,53 @@ seriesType :: Chart -> SeriesType
seriesType = SeriesType <<< show seriesType = SeriesType <<< show
-- | Scatter Dimension 2 data
type OptionalSeries =
( name :: String
, symbolSize :: Number
, itemStyle :: ItemStyle
-- ^ Graphic style of, *emphasis* is the style when it is highlighted, like being hovered by mouse, or highlighted via legend connect.
-- https://ecomfe.github.io/echarts-doc/public/en/option.html#series-scatter.itemStyle
, tooltip :: Tooltip
-- many more...
)
data Series data Series
unsafeSeries :: forall o. { | o } -> Series unsafeSeries :: forall o. Record o -> Series
unsafeSeries = unsafeCoerce unsafeSeries = unsafeCoerce
type RequiredD1 o = type RequiredSeriesD1 o =
{ "type" :: SeriesType { "type" :: SeriesType
, "data" :: Array DataS , "data" :: Array DataD1
| o | o
} }
type OptionalD1 = seriesD1 :: forall o. Optional o OptionalSeries => RequiredSeriesD1 o -> Series
( name :: String
-- many more...
)
seriesD1 :: forall o. Optional o OptionalD1 => RequiredD1 o -> Series
seriesD1 = unsafeSeries seriesD1 = unsafeSeries
seriesFunnelD1 :: forall o. Optional o OptionalD1 => Record o -> Array DataS -> Series seriesFunnelD1 :: forall o. Optional o OptionalSeries => Record o -> Array DataD1 -> Series
seriesFunnelD1 o ds = seriesD1 ((unsafeCoerce o :: RequiredD1 o) { "data" = ds, "type" = seriesType Funnel }) seriesFunnelD1 o ds = unsafeSeries (unsafeSet "data" ds (unsafeSet "type" (seriesType Funnel) o))
seriesBarD1 :: forall o. Optional o OptionalD1 => Record o -> Array DataS -> Series seriesBarD1 :: forall o. Optional o OptionalSeries => Record o -> Array DataD1 -> Series
seriesBarD1 o ds = seriesD1 ((unsafeCoerce o :: RequiredD1 o) { "data" = ds, "type" = seriesType Bar }) seriesBarD1 o ds = unsafeSeries (unsafeSet "data" ds (unsafeSet "type" (seriesType Bar) o))
seriesPieD1 :: forall o. Optional o OptionalD1 => Record o -> Array DataS -> Series seriesPieD1 :: forall o. Optional o OptionalSeries => Record o -> Array DataD1 -> Series
seriesPieD1 o ds = seriesD1 ((unsafeCoerce o :: RequiredD1 o) { "data" = ds, "type" = seriesType Pie }) seriesPieD1 o ds = unsafeSeries (unsafeSet "data" ds (unsafeSet "type" (seriesType Pie) o))
type RequiredD2 o = type RequiredSeriesD2 o =
{ "data" :: Array (Array Number) { "data" :: Array DataD2
, "type" :: SeriesType , "type" :: SeriesType
| o | o
} }
-- | Scatter Dimension 2 data seriesD2 :: forall o. Optional o OptionalSeries => RequiredSeriesD2 o -> Series
type OptionalD2 =
( name :: String
, symbolSize :: Number
, itemStyle :: ItemStyle
-- many more...
)
seriesD2 :: forall o. Optional o OptionalD2 => RequiredD2 o -> Series
seriesD2 = unsafeSeries seriesD2 = unsafeSeries
seriesScatterD2 :: forall o. Optional o OptionalD2 => Record o -> Array (Array Number) -> Series seriesScatterD2 :: forall o. Optional o OptionalSeries => Record o -> Array DataD2 -> Series
seriesScatterD2 o ds = seriesScatterD2 o ds =
seriesD2 ((unsafeCoerce o :: RequiredD2 o) { "data" = ds, "type" = seriesType Scatter }) unsafeCoerce (unsafeSet "data" ds (unsafeSet "type" (seriesType Scatter) o))
type Node = { name :: String} type Node = { name :: String}
type Link = { source :: String type Link = { source :: String
......
...@@ -5,7 +5,7 @@ import Prelude ...@@ -5,7 +5,7 @@ import Prelude
import Data.Maybe (Maybe) import Data.Maybe (Maybe)
import Gargantext.Components.Charts.Options.Color (Color) import Gargantext.Components.Charts.Options.Color (Color)
import Gargantext.Components.Charts.Options.Data (DataLegend, DataAxis) import Gargantext.Components.Charts.Options.Data (DataLegend, DataAxis)
import Gargantext.Components.Charts.Options.Font (TextStyle) import Gargantext.Components.Charts.Options.Font (TextStyle, Tooltip)
import Gargantext.Components.Charts.Options.Legend (LegendType, Orient, SelectedMode) import Gargantext.Components.Charts.Options.Legend (LegendType, Orient, SelectedMode)
import Gargantext.Components.Charts.Options.Position (LeftRelativePosition, Position, TopRelativePosition) import Gargantext.Components.Charts.Options.Position (LeftRelativePosition, Position, TopRelativePosition)
import Gargantext.Components.Charts.Options.Series (Series) import Gargantext.Components.Charts.Options.Series (Series)
...@@ -120,11 +120,6 @@ type Legend = ...@@ -120,11 +120,6 @@ type Legend =
, "data" :: Array DataLegend , "data" :: Array DataLegend
} }
type Tooltip =
{ trigger :: String
, formatter :: Maybe String -- TODO function
}
type AxisTick = type AxisTick =
{ alignWithLabel :: Boolean { alignWithLabel :: Boolean
} }
......
...@@ -2,9 +2,10 @@ module Gargantext.Pages.Corpus.Dashboard where ...@@ -2,9 +2,10 @@ module Gargantext.Pages.Corpus.Dashboard where
import Prelude hiding (div) import Prelude hiding (div)
import Data.Array (zip) import Data.Array (zipWith)
import Data.Tuple (Tuple(..)) import Data.Tuple (Tuple(..))
import Gargantext.Components.Charts.Options.ECharts (Options(..), chart, xAxis', yAxis') import Gargantext.Components.Charts.Options.ECharts (Options(..), chart, xAxis', yAxis', tooltipTriggerAxis)
import Gargantext.Components.Charts.Options.Data
import Gargantext.Components.Charts.Options.Series import Gargantext.Components.Charts.Options.Series
import Data.Int (toNumber) import Data.Int (toNumber)
import React.DOM (div, h1, text) import React.DOM (div, h1, text)
...@@ -28,9 +29,9 @@ render dispatch _ state _ = [ ...@@ -28,9 +29,9 @@ render dispatch _ state _ = [
] ]
where where
myData = [seriesBarD1 {name: "Bar Data"} myData = [seriesBarD1 {name: "Bar Data"}
[ {name: "val1", value: 50.0} [ dataSerie {name: "val1", value: 50.0}
, {name: "val2", value: 70.0} , dataSerie {name: "val2", value: 70.0}
, {name: "val3", value: 80.0} , dataSerie {name: "val3", value: 80.0}
] ]
] ]
...@@ -44,6 +45,7 @@ render dispatch _ state _ = [ ...@@ -44,6 +45,7 @@ render dispatch _ state _ = [
} }
, series : myData , series : myData
, addZoom : false , addZoom : false
, tooltip : tooltipTriggerAxis -- Necessary?
} }
----------------------------------------------------------------------------------------------------------- -----------------------------------------------------------------------------------------------------------
...@@ -53,8 +55,8 @@ naturePublis_x = ["Com","Articles","Thèses","Reports"] ...@@ -53,8 +55,8 @@ naturePublis_x = ["Com","Articles","Thèses","Reports"]
naturePublis_y' :: Array Int naturePublis_y' :: Array Int
naturePublis_y' = [23901,17417,1188,1176] naturePublis_y' = [23901,17417,1188,1176]
naturePublis_y :: Array {name :: String, value :: Number} naturePublis_y :: Array DataD1
naturePublis_y = map (\(Tuple n v) -> {name: n, value: toNumber v }) (zip naturePublis_x naturePublis_y') naturePublis_y = zipWith (\n v -> dataSerie {name: n, value: toNumber v }) naturePublis_x naturePublis_y'
naturePublis :: Options naturePublis :: Options
naturePublis = Options naturePublis = Options
...@@ -64,6 +66,7 @@ naturePublis = Options ...@@ -64,6 +66,7 @@ naturePublis = Options
, yAxis : yAxis' { position: "left", show: false } , yAxis : yAxis' { position: "left", show: false }
, series : [seriesFunnelD1 { name: "Funnel Data" } naturePublis_y] , series : [seriesFunnelD1 { name: "Funnel Data" } naturePublis_y]
, addZoom : false , addZoom : false
, tooltip : tooltipTriggerAxis -- Necessary?
} }
----------------------------------------------------------------------------------------------------------- -----------------------------------------------------------------------------------------------------------
...@@ -80,8 +83,9 @@ globalPublis = Options ...@@ -80,8 +83,9 @@ globalPublis = Options
, 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 : yAxis' { position: "left", show: true } , yAxis : yAxis' { position: "left", show: true }
, series : [seriesBarD1 {name: "Number of publication of IMT / year"} $ map (\n -> {name: "", value: toNumber n }) globalPublis_y] , series : [seriesBarD1 {name: "Number of publication of IMT / year"} $ map (\n -> dataSerie {name: "", value: toNumber n }) globalPublis_y]
, addZoom : true , addZoom : true
, tooltip : tooltipTriggerAxis -- Necessary?
} }
...@@ -96,8 +100,9 @@ distriBySchool = Options ...@@ -96,8 +100,9 @@ distriBySchool = Options
, subTitle : "Distribution by school" , subTitle : "Distribution by school"
, xAxis : xAxis' [] , xAxis : xAxis' []
, yAxis : yAxis' { position : "", show: false } , yAxis : yAxis' { position : "", show: false }
, series : [ seriesPieD1 {name: "Pie data"} (map (\(Tuple n v) -> {name: n, value: toNumber v}) distriBySchool_y)] , series : [ seriesPieD1 {name: "Pie data"} (map (\(Tuple n v) -> dataSerie {name: n, value: toNumber v}) distriBySchool_y)]
, addZoom : false , addZoom : false
, tooltip : tooltipTriggerAxis -- Necessary?
} }
scatterEx :: Options scatterEx :: Options
...@@ -106,11 +111,12 @@ scatterEx = Options ...@@ -106,11 +111,12 @@ scatterEx = Options
, subTitle : "Scatter subtitle" , subTitle : "Scatter subtitle"
, xAxis : xAxis' [] , xAxis : xAxis' []
, yAxis : yAxis' { position: "", show: true } , yAxis : yAxis' { position: "", show: true }
, series : [ seriesScatterD2 {name: "name1", symbolSize: 10.0} [[2.0,3.0],[3.0,4.0]] , series : [ seriesScatterD2 {name: "name1", symbolSize: 10.0} (dataSerieV <$> [[2.0,3.0],[3.0,4.0]])
, seriesScatterD2 {name: "name2", symbolSize: 5.0 } [[1.0,3.0],[5.0,4.0]] , seriesScatterD2 {name: "name2", symbolSize: 5.0 } (dataSerieV <$> [[1.0,3.0],[5.0,4.0]])
, seriesScatterD2 {name: "name3", symbolSize: 10.0} [[10.0,3.0],[8.0,4.0]] , seriesScatterD2 {name: "name3", symbolSize: 10.0} (dataSerieV <$> [[10.0,3.0],[8.0,4.0]])
] ]
, addZoom : false , addZoom : false
, tooltip : tooltipTriggerAxis -- Necessary?
} }
sankeyEx :: Options sankeyEx :: Options
...@@ -133,6 +139,7 @@ sankeyEx = Options ...@@ -133,6 +139,7 @@ sankeyEx = Options
, layout: "none" , layout: "none"
} }
] ]
, tooltip : tooltipTriggerAxis -- Necessary?
, addZoom : false , addZoom : false
} }
...@@ -189,6 +196,7 @@ treeMapEx = Options ...@@ -189,6 +196,7 @@ treeMapEx = Options
, yAxis : yAxis' { position: "", show: false } , yAxis : yAxis' { position: "", show: false }
, series : [mkTree TreeMap treeData] , series : [mkTree TreeMap treeData]
, addZoom : false , addZoom : false
, tooltip : tooltipTriggerAxis -- Necessary?
} }
treeEx :: Options treeEx :: Options
...@@ -199,6 +207,7 @@ treeEx = Options ...@@ -199,6 +207,7 @@ treeEx = Options
, yAxis : yAxis' { position: "", show: false } , yAxis : yAxis' { position: "", show: false }
, series : [mkTree TreeRadial treeData'] , series : [mkTree TreeRadial treeData']
, addZoom : false , addZoom : false
, tooltip : tooltipTriggerAxis -- Necessary?
} }
layoutDashboard :: Spec {} {} Void layoutDashboard :: Spec {} {} Void
......
...@@ -18,6 +18,8 @@ import Gargantext.Components.Charts.Options.ECharts ...@@ -18,6 +18,8 @@ import Gargantext.Components.Charts.Options.ECharts
import Gargantext.Components.Charts.Options.Type import Gargantext.Components.Charts.Options.Type
import Gargantext.Components.Charts.Options.Series import Gargantext.Components.Charts.Options.Series
import Gargantext.Components.Charts.Options.Color import Gargantext.Components.Charts.Options.Color
import Gargantext.Components.Charts.Options.Font
import Gargantext.Components.Charts.Options.Data
type Path = type Path =
{ corpusId :: Int { corpusId :: Int
...@@ -62,12 +64,13 @@ loadedMetricsSpec = simpleSpec defaultPerformAction render ...@@ -62,12 +64,13 @@ loadedMetricsSpec = simpleSpec defaultPerformAction render
scatterOptions :: Array Metric -> Options scatterOptions :: Array Metric -> Options
scatterOptions metrics = Options scatterOptions metrics = Options
{ mainTitle : "TODO Scatter test" { mainTitle : "Ngrams Selection Metrics"
, subTitle : "TODO Scatter subtitle" , subTitle : "Inc/Exc, Spe/Gen, TFICF"
, xAxis : xAxis { min: 0 } , xAxis : xAxis { min: 0 }
, yAxis : yAxis' { position : "", show: true } , yAxis : yAxis' { position : "", show: true }
, series : map2series $ metric2map metrics , series : map2series $ metric2map metrics
, addZoom : false , addZoom : false
, tooltip : mkTooltip { formatter: templateFormatter "{b0}" }
} }
where where
metric2map :: Array Metric -> Map TermList (Array Metric) metric2map :: Array Metric -> Map TermList (Array Metric)
...@@ -75,19 +78,22 @@ scatterOptions metrics = Options ...@@ -75,19 +78,22 @@ scatterOptions metrics = Options
--{- --{-
map2series :: Map TermList (Array Metric) -> Array Series map2series :: Map TermList (Array Metric) -> Array Series
map2series ms = toSeries =<< Map.toUnfoldable ms map2series ms = toSeries <$> Map.toUnfoldable ms
where where
-- TODO colors are not respected yet -- TODO colors are not respected yet
toSeries (Tuple k ms) = toSeries' color <$> ms toSeries (Tuple k ms) =
seriesScatterD2 {symbolSize: 5.0} (toSerie color <$> ms)
where where
color = color =
case k of case k of
StopTerm -> red StopTerm -> red
GraphTerm -> blue GraphTerm -> green
CandidateTerm -> magenta CandidateTerm -> grey
toSeries' color (Metric {label,x,y}) = toSerie color (Metric {label,x,y}) =
seriesScatterD2 {name: label, symbolSize: 5.0, itemStyle: itemStyle {color}} dataSerie { name: label, itemStyle: itemStyle {color}
[[x,y]] -- , label: {show: true}
, value: [x,y]
}
--} --}
getMetrics :: Path -> Aff Loaded getMetrics :: Path -> Aff Loaded
......
...@@ -1021,11 +1021,6 @@ base@^0.11.1: ...@@ -1021,11 +1021,6 @@ base@^0.11.1:
mixin-deep "^1.2.0" mixin-deep "^1.2.0"
pascalcase "^0.1.1" pascalcase "^0.1.1"
batch-processor@^1.0.0:
version "1.0.0"
resolved "https://registry.yarnpkg.com/batch-processor/-/batch-processor-1.0.0.tgz#75c95c32b748e0850d10c2b168f6bdbe9891ace8"
integrity sha1-dclcMrdI4IUNEMKxaPa9vpiRrOg=
beeper@^1.0.0: beeper@^1.0.0:
version "1.1.1" version "1.1.1"
resolved "https://registry.yarnpkg.com/beeper/-/beeper-1.1.1.tgz#e6d5ea8c5dad001304a70b22638447f69cb2f809" resolved "https://registry.yarnpkg.com/beeper/-/beeper-1.1.1.tgz#e6d5ea8c5dad001304a70b22638447f69cb2f809"
...@@ -2089,12 +2084,12 @@ echarts-for-react@^2.0.14: ...@@ -2089,12 +2084,12 @@ echarts-for-react@^2.0.14:
fast-deep-equal "^2.0.1" fast-deep-equal "^2.0.1"
size-sensor "^0.2.0" size-sensor "^0.2.0"
echarts@^3.8.5: echarts@^4.1.0:
version "3.8.5" version "4.1.0"
resolved "https://registry.yarnpkg.com/echarts/-/echarts-3.8.5.tgz#58e4a51d2743c6fb75257b0dc0a9cf9f5378ac0e" resolved "https://registry.yarnpkg.com/echarts/-/echarts-4.1.0.tgz#d588c95f73c1a9928b9c73d5b769751c3185bcdc"
integrity sha512-E+nnROMfCeiLeoT/fZyX8SE8mKzwkTjyemyoBF543oqjRtjTSKQAVDEihMXy4oC6pJS0tYGdMqCA2ATk8onyRg== integrity sha512-gP1e1fNnAj9KJpTDLXV21brklbfJlqeINmpQDJCDta9TX3cPoqyQOiDVcEPzbOVHqgBRgTOwNxC5iGwJ89014A==
dependencies: dependencies:
zrender "3.7.4" zrender "4.0.4"
ecstatic@^3.0.0: ecstatic@^3.0.0:
version "3.3.0" version "3.3.0"
...@@ -2106,13 +2101,6 @@ ecstatic@^3.0.0: ...@@ -2106,13 +2101,6 @@ ecstatic@^3.0.0:
minimist "^1.1.0" minimist "^1.1.0"
url-join "^2.0.5" url-join "^2.0.5"
element-resize-detector@latest:
version "1.1.14"
resolved "https://registry.yarnpkg.com/element-resize-detector/-/element-resize-detector-1.1.14.tgz#af064a0a618a820ad570a95c5eec5b77be0128c1"
integrity sha1-rwZKCmGKggrVcKlcXuxbd74BKME=
dependencies:
batch-processor "^1.0.0"
elliptic@^6.0.0: elliptic@^6.0.0:
version "6.4.1" version "6.4.1"
resolved "https://registry.yarnpkg.com/elliptic/-/elliptic-6.4.1.tgz#c2d0b7776911b86722c632c3c06c60f2f819939a" resolved "https://registry.yarnpkg.com/elliptic/-/elliptic-6.4.1.tgz#c2d0b7776911b86722c632c3c06c60f2f819939a"
...@@ -3557,7 +3545,7 @@ lodash.templatesettings@^3.0.0: ...@@ -3557,7 +3545,7 @@ lodash.templatesettings@^3.0.0:
lodash._reinterpolate "^3.0.0" lodash._reinterpolate "^3.0.0"
lodash.escape "^3.0.0" lodash.escape "^3.0.0"
lodash@^4.17.4, lodash@latest: lodash@^4.17.4:
version "4.17.5" version "4.17.5"
resolved "https://registry.yarnpkg.com/lodash/-/lodash-4.17.5.tgz#99a92d65c0272debe8c96b6057bc8fbfa3bed511" resolved "https://registry.yarnpkg.com/lodash/-/lodash-4.17.5.tgz#99a92d65c0272debe8c96b6057bc8fbfa3bed511"
integrity sha512-svL3uiZf1RwhH+cWrfZn3A4+U58wbP0tGVTLQPbjplZxZ8ROD9VLuNgsRniTlLe7OlSqR79RUehXgpBW/s0IQw== integrity sha512-svL3uiZf1RwhH+cWrfZn3A4+U58wbP0tGVTLQPbjplZxZ8ROD9VLuNgsRniTlLe7OlSqR79RUehXgpBW/s0IQw==
...@@ -4515,14 +4503,6 @@ react-dom@^16.4.2: ...@@ -4515,14 +4503,6 @@ react-dom@^16.4.2:
object-assign "^4.1.1" object-assign "^4.1.1"
prop-types "^15.6.0" prop-types "^15.6.0"
react-echarts-v3@^1.0.19:
version "1.0.19"
resolved "https://registry.yarnpkg.com/react-echarts-v3/-/react-echarts-v3-1.0.19.tgz#04148f16e3e7f01c2f6f3e6f0654bb32f238c2dc"
integrity sha512-2ro1lU/nfuIVxdrdvK0ZL2/tgxHmDMEeDY++JYfvDqZci//i9fGvBaKDJC/ZHgGmknffqXESoAOwZSgVgc0XOA==
dependencies:
element-resize-detector latest
lodash latest
"react-sigma@git://github.com/np/react-sigma.git#shouldComponentUpdate": "react-sigma@git://github.com/np/react-sigma.git#shouldComponentUpdate":
version "1.2.29" version "1.2.29"
resolved "git://github.com/np/react-sigma.git#0023eb24248c7bc61aec872bc26552e3d569b974" resolved "git://github.com/np/react-sigma.git#0023eb24248c7bc61aec872bc26552e3d569b974"
...@@ -5870,7 +5850,7 @@ zen-observable@^0.6.0, zen-observable@^0.6.1: ...@@ -5870,7 +5850,7 @@ zen-observable@^0.6.0, zen-observable@^0.6.1:
resolved "https://registry.yarnpkg.com/zen-observable/-/zen-observable-0.6.1.tgz#01dbed3bc8d02cbe9ee1112c83e04c807f647244" resolved "https://registry.yarnpkg.com/zen-observable/-/zen-observable-0.6.1.tgz#01dbed3bc8d02cbe9ee1112c83e04c807f647244"
integrity sha512-DKjFTL7siVLIUMZOFZ0alqMEdTsXPUxoCZzrvB2tdWEVN/6606Qh1nCfSTCAOZMrtcPzzFI3BXmwBKLAew52NA== integrity sha512-DKjFTL7siVLIUMZOFZ0alqMEdTsXPUxoCZzrvB2tdWEVN/6606Qh1nCfSTCAOZMrtcPzzFI3BXmwBKLAew52NA==
zrender@3.7.4: zrender@4.0.4:
version "3.7.4" version "4.0.4"
resolved "https://registry.yarnpkg.com/zrender/-/zrender-3.7.4.tgz#f847d53948481ef6d42906d1ea9aeec7acbefdf2" resolved "https://registry.yarnpkg.com/zrender/-/zrender-4.0.4.tgz#910e60d888f00c9599073f23758dd23345fe48fd"
integrity sha512-5Nz7+L1wIoL0+Pp/iOP56jD6eD017qC9VRSgUBheXBiAHgOBJZ4uh4/g6e83acIwa8RKSyZf/FlceKu5ntUuxQ== integrity sha512-03Vd/BDl/cPXp8E61f5+Xbgr/a4vDyFA+uUtUc1s+5KgcPbyY2m+78R/9LQwkR6QwFYHG8qk25Q8ESGs/qpkZw==
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