{-# LANGUAGE TemplateHaskell #-}
module Graphics.Rendering.Chart.Plot.Types(
Plot(..),
joinPlot,
ToPlot(..),
mapXY,
plot_render,
plot_legend,
plot_all_points,
) where
import Graphics.Rendering.Chart.Geometry
import Graphics.Rendering.Chart.Drawing
import Control.Lens
data Plot x y = Plot {
Plot x y -> PointMapFn x y -> BackendProgram ()
_plot_render :: PointMapFn x y -> BackendProgram (),
Plot x y -> [(String, Rect -> BackendProgram ())]
_plot_legend :: [ (String, Rect -> BackendProgram ()) ],
Plot x y -> ([x], [y])
_plot_all_points :: ([x],[y])
}
class ToPlot a where
toPlot :: a x y -> Plot x y
instance ToPlot Plot where
toPlot :: Plot x y -> Plot x y
toPlot Plot x y
p = Plot x y
p
joinPlot :: Plot x y -> Plot x y -> Plot x y
joinPlot :: Plot x y -> Plot x y -> Plot x y
joinPlot Plot{ _plot_render :: forall x y. Plot x y -> PointMapFn x y -> BackendProgram ()
_plot_render = PointMapFn x y -> BackendProgram ()
renderP
, _plot_legend :: forall x y. Plot x y -> [(String, Rect -> BackendProgram ())]
_plot_legend = [(String, Rect -> BackendProgram ())]
legendP
, _plot_all_points :: forall x y. Plot x y -> ([x], [y])
_plot_all_points = ([x]
xsP,[y]
ysP) }
Plot{ _plot_render :: forall x y. Plot x y -> PointMapFn x y -> BackendProgram ()
_plot_render = PointMapFn x y -> BackendProgram ()
renderQ
, _plot_legend :: forall x y. Plot x y -> [(String, Rect -> BackendProgram ())]
_plot_legend = [(String, Rect -> BackendProgram ())]
legendQ
, _plot_all_points :: forall x y. Plot x y -> ([x], [y])
_plot_all_points = ([x]
xsQ,[y]
ysQ) }
= 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 = \PointMapFn x y
a-> PointMapFn x y -> BackendProgram ()
renderP PointMapFn x y
a BackendProgram () -> BackendProgram () -> BackendProgram ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> PointMapFn x y -> BackendProgram ()
renderQ PointMapFn x y
a
, _plot_legend :: [(String, Rect -> BackendProgram ())]
_plot_legend = [(String, Rect -> BackendProgram ())]
legendP [(String, Rect -> BackendProgram ())]
-> [(String, Rect -> BackendProgram ())]
-> [(String, Rect -> BackendProgram ())]
forall a. [a] -> [a] -> [a]
++ [(String, Rect -> BackendProgram ())]
legendQ
, _plot_all_points :: ([x], [y])
_plot_all_points = ( [x]
xsP[x] -> [x] -> [x]
forall a. [a] -> [a] -> [a]
++[x]
xsQ, [y]
ysP[y] -> [y] -> [y]
forall a. [a] -> [a] -> [a]
++[y]
ysQ )
}
mapXY :: PointMapFn x y -> (x,y) -> Point
mapXY :: PointMapFn x y -> (x, y) -> Point
mapXY PointMapFn x y
f (x
x,y
y) = PointMapFn x y
f (x -> Limit x
forall a. a -> Limit a
LValue x
x, y -> Limit y
forall a. a -> Limit a
LValue y
y)
$( makeLenses ''Plot )