Commit d00d8d64 authored by Alexandre Delanoë's avatar Alexandre Delanoë

[CHART] Scatter multi-series.

parent 01820561
...@@ -26,7 +26,7 @@ endConfig = endConfig' V10 ...@@ -26,7 +26,7 @@ endConfig = endConfig' V10
endConfig' :: ApiVersion -> EndConfig endConfig' :: ApiVersion -> EndConfig
endConfig' v = { front : frontRelative endConfig' v = { front : frontRelative
, back : backDev v } , back : backLocal v }
------------------------------------------------------------------------ ------------------------------------------------------------------------
frontRelative :: Config frontRelative :: Config
......
module Gargantext.Pages.Corpus.Metrics where module Gargantext.Pages.Corpus.Metrics where
import Data.Set as Set
import Data.Array (foldl)
import Data.Tuple (Tuple(..))
import Data.Map (fromFoldableWith, Map(), keys, lookup)
import Data.Argonaut (class DecodeJson, decodeJson, (.?)) import Data.Argonaut (class DecodeJson, decodeJson, (.?))
import Data.Maybe (Maybe(..)) import Data.Maybe (Maybe(..), maybe)
import Effect.Aff (Aff) import Effect.Aff (Aff)
import Gargantext.Config -- (End(..), Path(..), TabType, toUrl) import Gargantext.Config -- (End(..), Path(..), TabType, toUrl)
import Gargantext.Config.REST (get) import Gargantext.Config.REST (get)
...@@ -54,19 +58,27 @@ loadedMetricsSpec = simpleSpec defaultPerformAction render ...@@ -54,19 +58,27 @@ loadedMetricsSpec = simpleSpec defaultPerformAction render
render :: Render {} (Loader.InnerProps Path Loaded ()) Void render :: Render {} (Loader.InnerProps Path Loaded ()) Void
render dispatch {loaded} {} _ = [chart (scatterOptions loaded)] render dispatch {loaded} {} _ = [chart (scatterOptions loaded)]
scatterOptions :: Loaded -> Options scatterOptions :: Array Metric -> Options
scatterOptions ds = Options scatterOptions ds = Options
{ mainTitle : "TODO Scatter test" { mainTitle : "TODO Scatter test"
, subTitle : "TODO Scatter subtitle" , subTitle : "TODO Scatter subtitle"
, xAxis : xAxis [] -- $ SeriesD2 $ seriesD2 Scatter 5.0 (_.x <$> ds) , xAxis : xAxis [] -- $ SeriesD2 $ seriesD2 Scatter 5.0 (_.x <$> ds)
, yAxis : [ SeriesD2 $ seriesD2 Scatter 5.0 (_y <$> ds) ] , yAxis : map2series ( metric2map ds )
, yAxisFormat : (YAxisFormat { position : "" , yAxisFormat : (YAxisFormat { position : ""
, visible : true , visible : true
}) })
, addZoom : false , addZoom : false
} }
where where
_y (Metric {x,y}) = [x,y] metric2map :: Array Metric -> Map TermList (Array (Array Number))
metric2map ds = fromFoldableWith (<>) $ map (\(Metric {x:x,y:y,cat:cat}) -> Tuple cat [[x,y]]) ds
--{-
map2series :: Map TermList (Array (Array Number)) -> Array Serie
map2series ms = map (\k -> maybe (toSeries [[]]) toSeries $ lookup k ms) ((Set.toUnfoldable $ keys ms) :: (Array TermList))
where
toSeries xs = SeriesD2 $ seriesD2 Scatter 5.0 xs
--}
getMetrics :: Path -> Aff Loaded getMetrics :: Path -> Aff Loaded
getMetrics {corpusId, listId, limit, tabType} = do getMetrics {corpusId, listId, limit, tabType} = do
......
...@@ -29,6 +29,7 @@ data TermList = GraphTerm | StopTerm | CandidateTerm ...@@ -29,6 +29,7 @@ data TermList = GraphTerm | StopTerm | CandidateTerm
-- TODO use generic JSON instance -- TODO use generic JSON instance
derive instance eqTermList :: Eq TermList derive instance eqTermList :: Eq TermList
derive instance ordTermList :: Ord TermList
instance encodeJsonTermList :: EncodeJson TermList where instance encodeJsonTermList :: EncodeJson TermList where
encodeJson GraphTerm = encodeJson "GraphTerm" encodeJson GraphTerm = encodeJson "GraphTerm"
......
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