Chart-1.9.1: A library for generating 2D Charts and Plots

Copyright(c) Tim Docker 2006 2014
LicenseBSD-style (see chart/COPYRIGHT)
Safe HaskellNone
LanguageHaskell98

Graphics.Rendering.Chart.Drawing

Contents

Description

This module contains basic types and functions used for drawing.

Note that Template Haskell is used to derive accessor functions (see Lens) for each field of the following data types:

These accessors are not shown in this API documentation. They have the same name as the field, but with the trailing underscore dropped. Hence for data field f_::F in type D, they have type

  f :: Control.Lens.Lens' D F
Synopsis

Point Types and Drawing

data PointShape Source #

The different shapes a point can have.

Constructors

PointShapeCircle

A circle.

PointShapePolygon Int Bool

Number of vertices and is right-side-up?

PointShapePlus

A plus sign.

PointShapeCross

A cross.

PointShapeStar

Combination of a cross and a plus.

PointShapeArrowHead Double 
PointShapeEllipse Double Double

Ratio of minor to major axis and rotation

data PointStyle Source #

Abstract data type for the style of a plotted point.

Constructors

PointStyle 

Fields

Instances
Default PointStyle Source #

Default style to use for points.

Instance details

Defined in Graphics.Rendering.Chart.Drawing

Methods

def :: PointStyle #

drawPoint Source #

Arguments

:: PointStyle

Style to use when rendering the point.

-> Point

Position of the point to render.

-> BackendProgram () 

Draw a single point at the given location.

Alignments and Paths

alignPath :: (Point -> Point) -> Path -> Path Source #

Align the path by applying the given function on all points.

alignFillPath :: Path -> BackendProgram Path Source #

Align the path using the environment's alignment function for coordinates. This is generally useful when filling. See alignPath and getCoordAlignFn.

alignStrokePath :: Path -> BackendProgram Path Source #

Align the path using the environment's alignment function for points. This is generally useful when stroking. See alignPath and getPointAlignFn.

alignFillPoints :: [Point] -> BackendProgram [Point] Source #

The points will be aligned by the getCoordAlignFn, so that when drawing bitmaps, the edges of the region will fall between pixels.

alignStrokePoints :: [Point] -> BackendProgram [Point] Source #

The points will be aligned by the getPointAlignFn, so that when drawing bitmaps, 1 pixel wide lines will be centred on the pixels.

alignFillPoint :: Point -> BackendProgram Point Source #

Align the point using the environment's alignment function for coordinates. See getCoordAlignFn.

alignStrokePoint :: Point -> BackendProgram Point Source #

Align the point using the environment's alignment function for points. See getPointAlignFn.

strokePointPath :: [Point] -> BackendProgram () Source #

Draw lines between the specified points.

fillPointPath :: [Point] -> BackendProgram () Source #

Fill the region with the given corners.

Transformation and Style Helpers

withRotation :: Double -> BackendProgram a -> BackendProgram a Source #

Apply a local rotation. The angle is given in radians.

withTranslation :: Point -> BackendProgram a -> BackendProgram a Source #

Apply a local translation.

withScale :: Vector -> BackendProgram a -> BackendProgram a Source #

Apply a local scale.

withScaleX :: Double -> BackendProgram a -> BackendProgram a Source #

Apply a local scale on the x-axis.

withScaleY :: Double -> BackendProgram a -> BackendProgram a Source #

Apply a local scale on the y-axis.

withPointStyle :: PointStyle -> BackendProgram a -> BackendProgram a Source #

Changes the LineStyle and FillStyle to comply with the given PointStyle.

Text Drawing

drawTextA :: HTextAnchor -> VTextAnchor -> Point -> String -> BackendProgram () Source #

Draw a line of text that is aligned at a different anchor point. See drawText.

drawTextR :: HTextAnchor -> VTextAnchor -> Double -> Point -> String -> BackendProgram () Source #

Draw a textual label anchored by one of its corners or edges, with rotation. Rotation angle is given in degrees, rotation is performed around anchor point. See drawText.

drawTextsR :: HTextAnchor -> VTextAnchor -> Double -> Point -> String -> BackendProgram () Source #

Draw a multi-line textual label anchored by one of its corners or edges, with rotation. Rotation angle is given in degrees, rotation is performed around anchor point. See drawText.

textDrawRect :: HTextAnchor -> VTextAnchor -> Point -> String -> BackendProgram Rect Source #

Return the bounding rectangle for a text string positioned where it would be drawn by drawText. See textSize.

textDimension :: String -> BackendProgram RectSize Source #

Get the width and height of the string when rendered. See textSize.

Style Helpers

defaultColorSeq :: [AlphaColour Double] Source #

The default sequence of colours to use when plotings different data sets in a graph.

solidLine Source #

Arguments

:: Double

Width of line.

-> AlphaColour Double

Colour of line.

-> LineStyle 

Create a solid line style (not dashed).

dashedLine Source #

Arguments

:: Double

Width of line.

-> [Double]

The dash pattern in device coordinates.

-> AlphaColour Double

Colour of line.

-> LineStyle 

Create a dashed line style.

filledCircles Source #

Arguments

:: Double

Radius of circle.

-> AlphaColour Double

Fill colour.

-> PointStyle 

Style for filled circle points.

hollowCircles Source #

Arguments

:: Double

Radius of circle.

-> Double

Thickness of line.

-> AlphaColour Double 
-> PointStyle 

Style for stroked circle points.

filledPolygon Source #

Arguments

:: Double

Radius of circle.

-> Int

Number of vertices.

-> Bool

Is right-side-up?

-> AlphaColour Double

Fill color.

-> PointStyle 

Style for filled polygon points.

hollowPolygon Source #

Arguments

:: Double

Radius of circle.

-> Double

Thickness of line.

-> Int

Number of vertices.

-> Bool

Is right-side-up?

-> AlphaColour Double

Colour of line.

-> PointStyle 

Style for stroked polygon points.

plusses Source #

Arguments

:: Double

Radius of tightest surrounding circle.

-> Double

Thickness of line.

-> AlphaColour Double

Color of line.

-> PointStyle 

Plus sign point style.

exes Source #

Arguments

:: Double

Radius of circle.

-> Double

Thickness of line.

-> AlphaColour Double

Color of line.

-> PointStyle 

Cross point style.

stars Source #

Arguments

:: Double

Radius of circle.

-> Double

Thickness of line.

-> AlphaColour Double

Color of line.

-> PointStyle 

Combination of plus and cross point style.

arrows Source #

Arguments

:: Double

Radius of circle.

-> Double

Rotation (Tau)

-> Double

Thickness of line.

-> AlphaColour Double

Color of line.

-> PointStyle 

solidFillStyle :: AlphaColour Double -> FillStyle Source #

Fill style that fill everything this the given colour.

Backend and general Types

Accessors