File: FillBetween.hs

package info (click to toggle)
haskell-chart 1.9.5-1
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid, trixie
  • size: 384 kB
  • sloc: haskell: 4,680; makefile: 3
file content (89 lines) | stat: -rw-r--r-- 2,925 bytes parent folder | download | duplicates (3)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
-----------------------------------------------------------------------------
-- |
-- Module      :  Graphics.Rendering.Chart.Plot.FillBetween
-- Copyright   :  (c) Tim Docker 2006, 2014
-- License     :  BSD-style (see chart/COPYRIGHT)
--
-- Plots that fill the area between two lines.
--
{-# LANGUAGE TemplateHaskell #-}

module Graphics.Rendering.Chart.Plot.FillBetween(
    PlotFillBetween(..),

    -- * Accessors
    -- | These accessors are generated by template haskell
    plot_fillbetween_title,
    plot_fillbetween_style,
    plot_fillbetween_line,
    plot_fillbetween_values,
) where

import Control.Lens
import Graphics.Rendering.Chart.Geometry
import Graphics.Rendering.Chart.Drawing
import Graphics.Rendering.Chart.Plot.Types
import Data.Colour (opaque)
import Data.Colour.SRGB (sRGB)
import Data.Default.Class

-- | Value specifying a plot filling the area between two sets of Y
--   coordinates, given common X coordinates.

data PlotFillBetween x y = PlotFillBetween {
    _plot_fillbetween_title  :: String,
    _plot_fillbetween_style  :: FillStyle,
    _plot_fillbetween_line  :: Maybe LineStyle,
    _plot_fillbetween_values :: [ (x, (y,y))]
}


instance ToPlot PlotFillBetween where
    toPlot p = Plot {
        _plot_render     = renderPlotFillBetween p,
        _plot_legend     = [(_plot_fillbetween_title p,renderPlotLegendFill p)],
        _plot_all_points = plotAllPointsFillBetween p
    }

renderPlotFillBetween :: PlotFillBetween x y -> PointMapFn x y -> BackendProgram ()
renderPlotFillBetween p =
    renderPlotFillBetween' p (_plot_fillbetween_values p)

renderPlotFillBetween' :: 
  PlotFillBetween x y 
  -> [(a, (b, b))]
  -> ((Limit a, Limit b) -> Point)
  -> BackendProgram ()
renderPlotFillBetween' _ [] _     = return ()
renderPlotFillBetween' p vs pmap  = 
  withFillStyle (_plot_fillbetween_style p) $ do
    ps <- alignFillPoints $ [p0] ++ p1s ++ reverse p2s ++ [p0]
    fillPointPath ps
    case _plot_fillbetween_line p of
      Nothing -> return ()
      Just lineStyle -> withLineStyle lineStyle $ strokePointPath ps
  where
    pmap'    = mapXY pmap
    (p0:p1s) = map pmap' [ (x,y1) | (x,(y1,_)) <- vs ]
    p2s      = map pmap' [ (x,y2) | (x,(_,y2)) <- vs ]

renderPlotLegendFill :: PlotFillBetween x y -> Rect -> BackendProgram ()
renderPlotLegendFill p r = 
  withFillStyle (_plot_fillbetween_style p) $ 
    fillPath (rectPath r)

plotAllPointsFillBetween :: PlotFillBetween x y -> ([x],[y])
plotAllPointsFillBetween p = ( [ x | (x,(_,_)) <- pts ]
                             , concat [ [y1,y2] | (_,(y1,y2)) <- pts ] )
  where
    pts = _plot_fillbetween_values p

instance Default (PlotFillBetween x y) where
  def = PlotFillBetween 
    { _plot_fillbetween_title  = ""
    , _plot_fillbetween_style  = solidFillStyle (opaque $ sRGB 0.5 0.5 1.0)
    , _plot_fillbetween_line   = Nothing
    , _plot_fillbetween_values = []
    }

$( makeLenses ''PlotFillBetween )