| Copyright | (c) Tim Docker 2014 | 
|---|---|
| License | BSD-style (see chart/COPYRIGHT) | 
| Safe Haskell | None | 
| Language | Haskell98 | 
Graphics.Rendering.Chart.Easy
Description
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.Lens 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
Synopsis
- module Control.Lens
- module Data.Default.Class
- alphaChannel :: AlphaColour a -> a
- atop :: Fractional a => AlphaColour a -> AlphaColour a -> AlphaColour a
- blend :: (Num a, AffineSpace f) => a -> f a -> f a -> f a
- withOpacity :: Num a => Colour a -> a -> AlphaColour a
- dissolve :: Num a => a -> AlphaColour a -> AlphaColour a
- opaque :: Num a => Colour a -> AlphaColour a
- alphaColourConvert :: (Fractional b, Real a) => AlphaColour a -> AlphaColour b
- transparent :: Num a => AlphaColour a
- black :: Num a => Colour a
- colourConvert :: (Fractional b, Real a) => Colour a -> Colour b
- data Colour a
- data AlphaColour a
- class AffineSpace (f :: Type -> Type) where- affineCombo :: Num a => [(a, f a)] -> f a -> f a
 
- class ColourOps (f :: Type -> Type) where
- 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
alphaChannel :: AlphaColour a -> a #
Returns the opacity of an AlphaColour.
atop :: Fractional a => AlphaColour a -> AlphaColour a -> AlphaColour a #
c1 `atop` c2 returns the AlphaColour produced by covering
 the portion of c2 visible by c1.
 The resulting alpha channel is always the same as the alpha channel
 of c2.
c1 `atop` (opaque c2) == c1 `over` (opaque c2) AlphaChannel (c1 `atop` c2) == AlphaChannel c2
blend :: (Num a, AffineSpace f) => a -> f a -> f a -> f a #
Compute the weighted average of two points. e.g.
blend 0.4 a b = 0.4*a + 0.6*b
The weight can be negative, or greater than 1.0; however, be aware that non-convex combinations may lead to out of gamut colours.
withOpacity :: Num a => Colour a -> a -> AlphaColour a #
Creates an AlphaColour from a Colour with a given opacity.
c `withOpacity` o == dissolve o (opaque c)
dissolve :: Num a => a -> AlphaColour a -> AlphaColour a #
Returns an AlphaColour more transparent by a factor of o.
opaque :: Num a => Colour a -> AlphaColour a #
Creates an opaque AlphaColour from a Colour.
alphaColourConvert :: (Fractional b, Real a) => AlphaColour a -> AlphaColour b #
Change the type used to represent the colour coordinates.
transparent :: Num a => AlphaColour a #
This AlphaColour is entirely transparent and has no associated
 colour channel.
colourConvert :: (Fractional b, Real a) => Colour a -> Colour b #
Change the type used to represent the colour coordinates.
This type represents the human preception of colour.
 The a parameter is a numeric type used internally for the
 representation.
The Monoid instance allows one to add colours, but beware that adding
 colours can take you out of gamut.  Consider using blend whenever
 possible.
data AlphaColour a #
This type represents a Colour that may be semi-transparent.
The Monoid instance allows you to composite colours.
x `mappend` y == x `over` y
To get the (pre-multiplied) colour channel of an AlphaColour c,
 simply composite c over black.
c `over` black
Instances
| AffineSpace AlphaColour | |
| Defined in Data.Colour.Internal Methods affineCombo :: Num a => [(a, AlphaColour a)] -> AlphaColour a -> AlphaColour a # | |
| ColourOps AlphaColour | |
| Defined in Data.Colour.Internal Methods over :: Num a => AlphaColour a -> AlphaColour a -> AlphaColour a # darken :: Num a => a -> AlphaColour a -> AlphaColour a # | |
| Eq a => Eq (AlphaColour a) | |
| Defined in Data.Colour.Internal Methods (==) :: AlphaColour a -> AlphaColour a -> Bool # (/=) :: AlphaColour a -> AlphaColour a -> Bool # | |
| Num a => Semigroup (AlphaColour a) | 
 | 
| Defined in Data.Colour.Internal Methods (<>) :: AlphaColour a -> AlphaColour a -> AlphaColour a # sconcat :: NonEmpty (AlphaColour a) -> AlphaColour a # stimes :: Integral b => b -> AlphaColour a -> AlphaColour a # | |
| Num a => Monoid (AlphaColour a) | |
| Defined in Data.Colour.Internal Methods mempty :: AlphaColour a # mappend :: AlphaColour a -> AlphaColour a -> AlphaColour a # mconcat :: [AlphaColour a] -> AlphaColour a # | |
class AffineSpace (f :: Type -> Type) where #
Methods
affineCombo :: Num a => [(a, f a)] -> f a -> f a #
Compute a affine Combination (weighted-average) of points. The last parameter will get the remaining weight. e.g.
affineCombo [(0.2,a), (0.3,b)] c == 0.2*a + 0.3*b + 0.5*c
Weights can be negative, or greater than 1.0; however, be aware that non-convex combinations may lead to out of gamut colours.
Instances
| AffineSpace Colour | |
| Defined in Data.Colour.Internal | |
| AffineSpace AlphaColour | |
| Defined in Data.Colour.Internal Methods affineCombo :: Num a => [(a, AlphaColour a)] -> AlphaColour a -> AlphaColour a # | |
class ColourOps (f :: Type -> Type) where #
Methods
darken :: Num a => a -> f a -> f a #
darken s c blends a colour with black without changing it's opacity.
For Colour, darken s c = blend s c mempty
Instances
| ColourOps Colour | |
| ColourOps AlphaColour | |
| Defined in Data.Colour.Internal Methods over :: Num a => AlphaColour a -> AlphaColour a -> AlphaColour a # darken :: Num a => a -> AlphaColour a -> AlphaColour a # | |
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