module Graphics.Rendering.Chart.Plot.ErrBars(
PlotErrBars(..),
defaultPlotErrBars,
ErrPoint(..),
ErrValue(..),
symErrPoint,
plot_errbars_title,
plot_errbars_line_style,
plot_errbars_tick_length,
plot_errbars_overhang,
plot_errbars_values,
) where
import Control.Lens
import Data.Monoid
import Graphics.Rendering.Chart.Geometry
import Graphics.Rendering.Chart.Drawing
import Graphics.Rendering.Chart.Renderable
import Graphics.Rendering.Chart.Plot.Types
import Data.Colour (opaque)
import Data.Colour.Names (black, blue)
import Data.Colour.SRGB (sRGB)
import Data.Default.Class
data ErrValue x = ErrValue {
ev_low :: x,
ev_best :: x,
ev_high :: x
} deriving Show
data ErrPoint x y = ErrPoint {
ep_x :: ErrValue x,
ep_y :: ErrValue y
} deriving Show
symErrPoint :: (Num a, Num b) => a -> b -> a -> b -> ErrPoint a b
symErrPoint x y dx dy = ErrPoint (ErrValue (xdx) x (x+dx))
(ErrValue (ydy) y (y+dy))
data PlotErrBars x y = PlotErrBars {
_plot_errbars_title :: String,
_plot_errbars_line_style :: LineStyle,
_plot_errbars_tick_length :: Double,
_plot_errbars_overhang :: Double,
_plot_errbars_values :: [ErrPoint x y]
}
instance ToPlot PlotErrBars where
toPlot p = Plot {
_plot_render = renderPlotErrBars p,
_plot_legend = [(_plot_errbars_title p, renderPlotLegendErrBars p)],
_plot_all_points = ( concat [ [ev_low x,ev_high x]
| ErrPoint x _ <- pts ]
, concat [ [ev_low y,ev_high y]
| ErrPoint _ y <- pts ] )
}
where
pts = _plot_errbars_values p
renderPlotErrBars :: PlotErrBars x y -> PointMapFn x y -> ChartBackend ()
renderPlotErrBars p pmap = do
mapM_ (drawErrBar.epmap) (_plot_errbars_values p)
where
epmap (ErrPoint (ErrValue xl x xh) (ErrValue yl y yh)) =
ErrPoint (ErrValue xl' x' xh') (ErrValue yl' y' yh')
where (Point x' y') = pmap' (x,y)
(Point xl' yl') = pmap' (xl,yl)
(Point xh' yh') = pmap' (xh,yh)
drawErrBar = drawErrBar0 p
pmap' = mapXY pmap
drawErrBar0 ps (ErrPoint (ErrValue xl x xh) (ErrValue yl y yh)) = do
let tl = _plot_errbars_tick_length ps
let oh = _plot_errbars_overhang ps
withLineStyle (_plot_errbars_line_style ps) $ do
strokePath $ moveTo' (xloh) y
<> lineTo' (xh+oh) y
<> moveTo' x (yloh)
<> lineTo' x (yh+oh)
<> moveTo' xl (ytl)
<> lineTo' xl (y+tl)
<> moveTo' (xtl) yl
<> lineTo' (x+tl) yl
<> moveTo' xh (ytl)
<> lineTo' xh (y+tl)
<> moveTo' (xtl) yh
<> lineTo' (x+tl) yh
renderPlotLegendErrBars :: PlotErrBars x y -> Rect -> ChartBackend ()
renderPlotLegendErrBars p r@(Rect p1 p2) = do
drawErrBar (symErrPoint (p_x p1) ((p_y p1 + p_y p2)/2) dx dx)
drawErrBar (symErrPoint ((p_x p1 + p_x p2)/2) ((p_y p1 + p_y p2)/2) dx dx)
drawErrBar (symErrPoint (p_x p2) ((p_y p1 + p_y p2)/2) dx dx)
where
drawErrBar = drawErrBar0 p
dx = min ((p_x p2 p_x p1)/6) ((p_y p2 p_y p1)/2)
defaultPlotErrBars :: PlotErrBars x y
defaultPlotErrBars = def
instance Default (PlotErrBars x y) where
def = PlotErrBars
{ _plot_errbars_title = ""
, _plot_errbars_line_style = solidLine 1 $ opaque blue
, _plot_errbars_tick_length = 3
, _plot_errbars_overhang = 0
, _plot_errbars_values = []
}
$( makeLenses ''PlotErrBars )