Hi Tim,

Thank you for commenting. As I said before, Chart is a wonderful library. Although it has most features we need, I personally feel that it's cumbersome to make plots or define new plots by Chart. So I would like to experiment a new library which makes this process more natural and intuitive. For example, to make a plot, we can

1. generate axes from data by calling:

    xAxis = realAxis rangeOfX padding opts
  yAxis = realAxis rangeOfY padding opts

2. Assemble axes:

area = plotArea 5.5 4.8
       ( yAxis  -- left axis
       , def  -- top axis, using default axis which is a line
       , def  -- right axis
       , xAxis -- bottom axis
       )

3. make delayed plots which are functions. Given a point map provided by plot area, they can generate actual plots.
 
   ps = points xs ys def
   l = line xs ys def

3. attach any number and any types of plots to plot area:

    plot = area <+ (ps, BL) <+ (l, BL)
    
    We have four axes in plot area, so you can attach plots to plot area by any two of the axes, for example, you can do

    area <+ (ps, BR) <+ (l, BL) <+ (l, TL) <+ (l, TR)

Each intermediate step can be easily customized separately and independently without worrying about other parts. And styling can be done by calling APIs of Diagrams.


On Sun, May 4, 2014 at 4:10 AM, Tim Docker <tim@dockerz.net> wrote:

On 3 May 2014, at 7:44 am, Kai Zhang <kai@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))