{-# 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 = forall a l. State CState a -> EC l a
liftCState forall a b. (a -> b) -> a -> b
$ Lens' CState [AlphaColour Double]
colors forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= forall a. [a] -> [a]
cycle [AlphaColour Double]
cs
setShapes :: [PointShape] -> EC l ()
setShapes :: forall l. [PointShape] -> EC l ()
setShapes [PointShape]
ps = forall a l. State CState a -> EC l a
liftCState forall a b. (a -> b) -> a -> b
$ Lens' CState [PointShape]
shapes forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= forall a. [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 = forall l1 a l2. Default l1 => EC l1 a -> EC l2 l1
liftEC forall a b. (a -> b) -> a -> b
$ do
AlphaColour Double
color <- forall l. EC l (AlphaColour Double)
takeColor
forall x y. Lens' (PlotLines x y) String
plot_lines_title forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= String
title
forall x y. Lens' (PlotLines x y) [[(x, y)]]
plot_lines_values forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= [[(x, y)]]
values
forall x y. Lens' (PlotLines x y) LineStyle
plot_lines_style forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens' LineStyle (AlphaColour Double)
line_color forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= AlphaColour Double
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 = forall l1 a l2. Default l1 => EC l1 a -> EC l2 l1
liftEC forall a b. (a -> b) -> a -> b
$ do
AlphaColour Double
color <- forall l. EC l (AlphaColour Double)
takeColor
PointShape
shape <- forall l. EC l PointShape
takeShape
forall x1 y1 x2 y2.
Lens (PlotPoints x1 y1) (PlotPoints x2 y2) [(x1, y1)] [(x2, y2)]
plot_points_values forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= [(x, y)]
values
forall x y. Lens' (PlotPoints x y) String
plot_points_title forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= String
title
forall x y. Lens' (PlotPoints x y) PointStyle
plot_points_style forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens' PointStyle (AlphaColour Double)
point_color forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= AlphaColour Double
color
forall x y. Lens' (PlotPoints x y) PointStyle
plot_points_style forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens' PointStyle PointShape
point_shape forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= PointShape
shape
forall x y. Lens' (PlotPoints x y) PointStyle
plot_points_style forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens' PointStyle Double
point_radius forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= Double
2
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (PointShape -> Bool
isFilled PointShape
shape) forall a b. (a -> b) -> a -> b
$ do
forall x y. Lens' (PlotPoints x y) PointStyle
plot_points_style forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens' PointStyle (AlphaColour Double)
point_border_color forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= AlphaColour Double
color
forall x y. Lens' (PlotPoints x y) PointStyle
plot_points_style forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens' PointStyle Double
point_border_width forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= Double
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 = forall l1 a l2. Default l1 => EC l1 a -> EC l2 l1
liftEC forall a b. (a -> b) -> a -> b
$ do
[(FillStyle, Maybe LineStyle)]
styles <- forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
sequence [forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap AlphaColour Double -> (FillStyle, Maybe LineStyle)
mkStyle forall l. EC l (AlphaColour Double)
takeColor | String
_ <- [String]
titles]
forall x y. Lens' (PlotBars x y) [String]
plot_bars_titles forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= [String]
titles
forall x y. Lens' (PlotBars x y) [(x, [y])]
plot_bars_values forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= [(x, [y])]
vals
forall x y. Lens' (PlotBars x y) PlotBarsStyle
plot_bars_style forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= PlotBarsStyle
BarsClustered
forall x y. Lens' (PlotBars x y) PlotBarsSpacing
plot_bars_spacing forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= Double -> Double -> PlotBarsSpacing
BarsFixGap Double
30 Double
5
forall x y. Lens' (PlotBars x y) [(FillStyle, Maybe LineStyle)]
plot_bars_item_styles forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= [(FillStyle, Maybe LineStyle)]
styles
where
mkStyle :: AlphaColour Double -> (FillStyle, Maybe LineStyle)
mkStyle AlphaColour Double
c = (AlphaColour Double -> FillStyle
solidFillStyle AlphaColour Double
c, forall a. a -> Maybe a
Just (Double -> AlphaColour Double -> LineStyle
solidLine Double
1.0 forall a b. (a -> b) -> a -> b
$ forall a. Num a => Colour a -> AlphaColour a
opaque forall a. Num a => Colour a
black))