[Haskell-cafe] Experimenting a new plotting library
Tim Docker
tim at dockerz.net
Sun May 4 11:10:00 UTC 2014
On 3 May 2014, at 7:44 am, Kai Zhang <kai at kzhang.org> wrote:
> 1. There is few plotting library written in pure Haskell
> 2. Haskell-chart, one of the most featured library, is hard to extend and there is no straightforward way to compose or modify the plots generated by this library.
The chart library is pure haskell when using the diagrams backend.
What do you mean by compose or modify the plots? It’s reasonably straightforward to have it produce a diagram, which can then be composed or modified with any of the diagrams tools. Some sample code is shown below.
Tim (chart library maintainer)
{-# LANGUAGE FlexibleContexts #-}
import Graphics.Rendering.Chart
import Data.Colour
import Data.Colour.Names
import Data.Colour.SRGB
import Control.Lens
import Data.Default.Class
import Graphics.Rendering.Chart.Backend.Diagrams
import qualified Diagrams.Prelude as D
import qualified Diagrams.Backend.SVG as D
chart :: Renderable (LayoutPick Double Double Double)
chart = layoutToRenderable
$ layout_title .~ "Amplitude Modulation"
$ layout_plots .~ [toPlot sinusoid1]
$ layout_plot_background .~ Just (solidFillStyle $ opaque white)
$ def
where
am x = (sin (x*pi/45) + 1) / 2 * (sin (x*pi/5))
sinusoid1 = plot_lines_values .~ [[ (x,(am x)) | x <- [0,(0.5)..400]]]
$ plot_lines_style .~ solidLine 1 (opaque blue)
$ plot_lines_title .~"am"
$ def
mkDiagram :: (D.Backend b D.R2, D.Renderable (D.Path D.R2) b) => IO (D.Diagram b D.R2)
mkDiagram = do
env <- defaultEnv vectorAlignmentFns 800 400
return (fst (runBackendR env chart))
More information about the Haskell-Cafe
mailing list