{-# LANGUAGE ScopedTypeVariables, FlexibleInstances #-}
module Graphics.Rendering.Chart.Easy(
module Control.Lens,
module Data.Default.Class,
module Data.Colour,
module Data.Colour.Names,
module Graphics.Rendering.Chart,
module Graphics.Rendering.Chart.State,
line,
points,
bars,
setColors,
setShapes
) where
import Control.Lens
import Control.Monad(unless)
import Data.Default.Class
import Data.Colour hiding (over)
import Data.Colour.Names
import Graphics.Rendering.Chart
import Graphics.Rendering.Chart.State
setColors :: [AlphaColour Double] -> EC l ()
setColors :: forall l. [AlphaColour Double] -> EC l ()
setColors [AlphaColour Double]
cs = State CState () -> EC l ()
forall a l. State CState a -> EC l a
liftCState (State CState () -> EC l ()) -> State CState () -> EC l ()
forall a b. (a -> b) -> a -> b
$ ([AlphaColour Double] -> Identity [AlphaColour Double])
-> CState -> Identity CState
Lens' CState [AlphaColour Double]
colors (([AlphaColour Double] -> Identity [AlphaColour Double])
-> CState -> Identity CState)
-> [AlphaColour Double] -> State CState ()
forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= [AlphaColour Double] -> [AlphaColour Double]
forall a. HasCallStack => [a] -> [a]
cycle [AlphaColour Double]
cs
setShapes :: [PointShape] -> EC l ()
setShapes :: forall l. [PointShape] -> EC l ()
setShapes [PointShape]
ps = State CState () -> EC l ()
forall a l. State CState a -> EC l a
liftCState (State CState () -> EC l ()) -> State CState () -> EC l ()
forall a b. (a -> b) -> a -> b
$ ([PointShape] -> Identity [PointShape])
-> CState -> Identity CState
Lens' CState [PointShape]
shapes (([PointShape] -> Identity [PointShape])
-> CState -> Identity CState)
-> [PointShape] -> State CState ()
forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= [PointShape] -> [PointShape]
forall a. HasCallStack => [a] -> [a]
cycle [PointShape]
ps
line :: String -> [[(x,y)]] -> EC l (PlotLines x y)
line :: forall x y l. String -> [[(x, y)]] -> EC l (PlotLines x y)
line String
title [[(x, y)]]
values = EC (PlotLines x y) () -> EC l (PlotLines x y)
forall l1 a l2. Default l1 => EC l1 a -> EC l2 l1
liftEC (EC (PlotLines x y) () -> EC l (PlotLines x y))
-> EC (PlotLines x y) () -> EC l (PlotLines x y)
forall a b. (a -> b) -> a -> b
$ do
color <- EC (PlotLines x y) (AlphaColour Double)
forall l. EC l (AlphaColour Double)
takeColor
plot_lines_title .= title
plot_lines_values .= values
plot_lines_style . line_color .= color
points :: String -> [(x,y)] -> EC l (PlotPoints x y)
points :: forall x y l. String -> [(x, y)] -> EC l (PlotPoints x y)
points String
title [(x, y)]
values = EC (PlotPoints x y) () -> EC l (PlotPoints x y)
forall l1 a l2. Default l1 => EC l1 a -> EC l2 l1
liftEC (EC (PlotPoints x y) () -> EC l (PlotPoints x y))
-> EC (PlotPoints x y) () -> EC l (PlotPoints x y)
forall a b. (a -> b) -> a -> b
$ do
color <- EC (PlotPoints x y) (AlphaColour Double)
forall l. EC l (AlphaColour Double)
takeColor
shape <- takeShape
plot_points_values .= values
plot_points_title .= title
plot_points_style . point_color .= color
plot_points_style . point_shape .= shape
plot_points_style . point_radius .= 2
unless (isFilled shape) $ do
plot_points_style . point_border_color .= color
plot_points_style . point_border_width .= 1
isFilled :: PointShape -> Bool
isFilled :: PointShape -> Bool
isFilled PointShape
PointShapeCircle = Bool
True
isFilled PointShapePolygon{} = Bool
True
isFilled PointShape
_ = Bool
False
bars :: (PlotValue x, BarsPlotValue y) => [String] -> [(x,[y])] -> EC l (PlotBars x y)
bars :: forall x y l.
(PlotValue x, BarsPlotValue y) =>
[String] -> [(x, [y])] -> EC l (PlotBars x y)
bars [String]
titles [(x, [y])]
vals = EC (PlotBars x y) () -> EC l (PlotBars x y)
forall l1 a l2. Default l1 => EC l1 a -> EC l2 l1
liftEC (EC (PlotBars x y) () -> EC l (PlotBars x y))
-> EC (PlotBars x y) () -> EC l (PlotBars x y)
forall a b. (a -> b) -> a -> b
$ do
styles <- [StateT
(PlotBars x y)
(StateT CState Identity)
(FillStyle, Maybe LineStyle)]
-> StateT
(PlotBars x y)
(StateT CState Identity)
[(FillStyle, Maybe LineStyle)]
forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
forall (m :: * -> *) a. Monad m => [m a] -> m [a]
sequence [(AlphaColour Double -> (FillStyle, Maybe LineStyle))
-> StateT
(PlotBars x y) (StateT CState Identity) (AlphaColour Double)
-> StateT
(PlotBars x y)
(StateT CState Identity)
(FillStyle, Maybe LineStyle)
forall a b.
(a -> b)
-> StateT (PlotBars x y) (StateT CState Identity) a
-> StateT (PlotBars x y) (StateT CState Identity) b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap AlphaColour Double -> (FillStyle, Maybe LineStyle)
mkStyle StateT (PlotBars x y) (StateT CState Identity) (AlphaColour Double)
forall l. EC l (AlphaColour Double)
takeColor | String
_ <- [String]
titles]
plot_bars_titles .= titles
plot_bars_values .= vals
plot_bars_style .= BarsClustered
plot_bars_spacing .= BarsFixGap 30 5
plot_bars_item_styles .= styles
where
mkStyle :: AlphaColour Double -> (FillStyle, Maybe LineStyle)
mkStyle AlphaColour Double
c = (AlphaColour Double -> FillStyle
solidFillStyle AlphaColour Double
c, LineStyle -> Maybe LineStyle
forall a. a -> Maybe a
Just (Double -> AlphaColour Double -> LineStyle
solidLine Double
1.0 (AlphaColour Double -> LineStyle)
-> AlphaColour Double -> LineStyle
forall a b. (a -> b) -> a -> b
$ Colour Double -> AlphaColour Double
forall a. Num a => Colour a -> AlphaColour a
opaque Colour Double
forall a. Num a => Colour a
black))