Copyright | (c) Tim Docker 2014 |
---|---|
License | BSD-style (see chart/COPYRIGHT) |
Safe Haskell | None |
Language | Haskell98 |
A high level API for generating a plot quickly.
Importing the Easy module brings into scope all core functions and types required for working with the chart library. This includes key external dependencies such as Control.Len and Data.Colour. The module also provides several helper functions for quickly generating common plots. Note that chart backends must still be explicitly imported, as some backends cannot be built on all platforms.
Example usage:
import Graphics.Rendering.Chart.Easy import Graphics.Rendering.Chart.Backend.Cairo signal :: [Double] -> [(Double,Double)] signal xs = [ (x,(sin (x*3.14159/45) + 1) / 2 * (sin (x*3.14159/5))) | x <- xs ] main = toFile def "example.png" $ do layout_title .= "Amplitude Modulation" plot (line "am" [signal [0,(0.5)..400]]) plot (points "am points" (signal [0,7..400]))
More examples can be found on the library's wiki
- module Control.Lens
- module Data.Default.Class
- module Data.Colour
- module Data.Colour.Names
- module Graphics.Rendering.Chart
- module Graphics.Rendering.Chart.State
- line :: String -> [[(x, y)]] -> EC l (PlotLines x y)
- points :: String -> [(x, y)] -> EC l (PlotPoints x y)
- bars :: (PlotValue x, BarsPlotValue y) => [String] -> [(x, [y])] -> EC l (PlotBars x y)
- setColors :: [AlphaColour Double] -> EC l ()
- setShapes :: [PointShape] -> EC l ()
Documentation
module Control.Lens
module Data.Default.Class
module Data.Colour
module Data.Colour.Names
module Graphics.Rendering.Chart
line :: String -> [[(x, y)]] -> EC l (PlotLines x y) Source #
Constuct a line plot with the given title and data, using the next available color.
points :: String -> [(x, y)] -> EC l (PlotPoints x y) Source #
Construct a scatter plot with the given title and data, using the next available color and point shape.
bars :: (PlotValue x, BarsPlotValue y) => [String] -> [(x, [y])] -> EC l (PlotBars x y) Source #
Construct a bar chart with the given titles and data, using the next available colors
setColors :: [AlphaColour Double] -> EC l () Source #
Set the contents of the colour source, for subsequent plots
setShapes :: [PointShape] -> EC l () Source #
Set the contents of the shape source, for subsequent plots