{-# LANGUAGE TemplateHaskell #-}
module Graphics.Rendering.Chart.Plot.Points(
PlotPoints(..),
plot_points_title,
plot_points_style,
plot_points_values,
) where
import Control.Lens
import Graphics.Rendering.Chart.Geometry
import Graphics.Rendering.Chart.Drawing
import Graphics.Rendering.Chart.Plot.Types
import Data.Default.Class
data PlotPoints x y = PlotPoints {
PlotPoints x y -> String
_plot_points_title :: String,
PlotPoints x y -> PointStyle
_plot_points_style :: PointStyle,
PlotPoints x y -> [(x, y)]
_plot_points_values :: [(x,y)]
}
instance ToPlot PlotPoints where
toPlot :: PlotPoints x y -> Plot x y
toPlot PlotPoints x y
p = Plot :: forall x y.
(PointMapFn x y -> BackendProgram ())
-> [(String, Rect -> BackendProgram ())] -> ([x], [y]) -> Plot x y
Plot {
_plot_render :: PointMapFn x y -> BackendProgram ()
_plot_render = PlotPoints x y -> PointMapFn x y -> BackendProgram ()
forall x y. PlotPoints x y -> PointMapFn x y -> BackendProgram ()
renderPlotPoints PlotPoints x y
p,
_plot_legend :: [(String, Rect -> BackendProgram ())]
_plot_legend = [(PlotPoints x y -> String
forall x y. PlotPoints x y -> String
_plot_points_title PlotPoints x y
p, PlotPoints x y -> Rect -> BackendProgram ()
forall x y. PlotPoints x y -> Rect -> BackendProgram ()
renderPlotLegendPoints PlotPoints x y
p)],
_plot_all_points :: ([x], [y])
_plot_all_points = (((x, y) -> x) -> [(x, y)] -> [x]
forall a b. (a -> b) -> [a] -> [b]
map (x, y) -> x
forall a b. (a, b) -> a
fst [(x, y)]
pts, ((x, y) -> y) -> [(x, y)] -> [y]
forall a b. (a -> b) -> [a] -> [b]
map (x, y) -> y
forall a b. (a, b) -> b
snd [(x, y)]
pts)
}
where
pts :: [(x, y)]
pts = PlotPoints x y -> [(x, y)]
forall x y. PlotPoints x y -> [(x, y)]
_plot_points_values PlotPoints x y
p
renderPlotPoints :: PlotPoints x y -> PointMapFn x y -> BackendProgram ()
renderPlotPoints :: PlotPoints x y -> PointMapFn x y -> BackendProgram ()
renderPlotPoints PlotPoints x y
p PointMapFn x y
pmap =
((x, y) -> BackendProgram ()) -> [(x, y)] -> BackendProgram ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (PointStyle -> Point -> BackendProgram ()
drawPoint PointStyle
ps (Point -> BackendProgram ())
-> ((x, y) -> Point) -> (x, y) -> BackendProgram ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (x, y) -> Point
pmap') (PlotPoints x y -> [(x, y)]
forall x y. PlotPoints x y -> [(x, y)]
_plot_points_values PlotPoints x y
p)
where
pmap' :: (x, y) -> Point
pmap' = PointMapFn x y -> (x, y) -> Point
forall x y. PointMapFn x y -> (x, y) -> Point
mapXY PointMapFn x y
pmap
ps :: PointStyle
ps = PlotPoints x y -> PointStyle
forall x y. PlotPoints x y -> PointStyle
_plot_points_style PlotPoints x y
p
renderPlotLegendPoints :: PlotPoints x y -> Rect -> BackendProgram ()
renderPlotLegendPoints :: PlotPoints x y -> Rect -> BackendProgram ()
renderPlotLegendPoints PlotPoints x y
p (Rect Point
p1 Point
p2) = do
PointStyle -> Point -> BackendProgram ()
drawPoint PointStyle
ps (Double -> Double -> Point
Point (Point -> Double
p_x Point
p1) Double
y)
PointStyle -> Point -> BackendProgram ()
drawPoint PointStyle
ps (Double -> Double -> Point
Point ((Point -> Double
p_x Point
p1 Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Point -> Double
p_x Point
p2)Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/Double
2) Double
y)
PointStyle -> Point -> BackendProgram ()
drawPoint PointStyle
ps (Double -> Double -> Point
Point (Point -> Double
p_x Point
p2) Double
y)
where
ps :: PointStyle
ps = PlotPoints x y -> PointStyle
forall x y. PlotPoints x y -> PointStyle
_plot_points_style PlotPoints x y
p
y :: Double
y = (Point -> Double
p_y Point
p1 Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Point -> Double
p_y Point
p2)Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/Double
2
instance Default (PlotPoints x y) where
def :: PlotPoints x y
def = PlotPoints :: forall x y. String -> PointStyle -> [(x, y)] -> PlotPoints x y
PlotPoints
{ _plot_points_title :: String
_plot_points_title = String
""
, _plot_points_style :: PointStyle
_plot_points_style = PointStyle
forall a. Default a => a
def
, _plot_points_values :: [(x, y)]
_plot_points_values = []
}
$( makeLenses ''PlotPoints )