Safe Haskell | None |
---|
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
- data PointShape
- data PointStyle = PointStyle {}
- drawPoint :: PointStyle -> Point -> ChartBackend ()
- defaultPointStyle :: PointStyle
- alignPath :: (Point -> Point) -> Path -> Path
- alignFillPath :: Path -> ChartBackend Path
- alignStrokePath :: Path -> ChartBackend Path
- alignFillPoints :: [Point] -> ChartBackend [Point]
- alignStrokePoints :: [Point] -> ChartBackend [Point]
- alignFillPoint :: Point -> ChartBackend Point
- alignStrokePoint :: Point -> ChartBackend Point
- strokePointPath :: [Point] -> ChartBackend ()
- fillPointPath :: [Point] -> ChartBackend ()
- withRotation :: Double -> ChartBackend a -> ChartBackend a
- withTranslation :: Point -> ChartBackend a -> ChartBackend a
- withScale :: Vector -> ChartBackend a -> ChartBackend a
- withScaleX :: Double -> ChartBackend a -> ChartBackend a
- withScaleY :: Double -> ChartBackend a -> ChartBackend a
- withPointStyle :: PointStyle -> ChartBackend a -> ChartBackend a
- withDefaultStyle :: ChartBackend a -> ChartBackend a
- drawTextA :: HTextAnchor -> VTextAnchor -> Point -> String -> ChartBackend ()
- drawTextR :: HTextAnchor -> VTextAnchor -> Double -> Point -> String -> ChartBackend ()
- drawTextsR :: HTextAnchor -> VTextAnchor -> Double -> Point -> String -> ChartBackend ()
- textDrawRect :: HTextAnchor -> VTextAnchor -> Point -> String -> ChartBackend Rect
- textDimension :: String -> ChartBackend RectSize
- defaultColorSeq :: [AlphaColour Double]
- solidLine :: Double -> AlphaColour Double -> LineStyle
- dashedLine :: Double -> [Double] -> AlphaColour Double -> LineStyle
- filledCircles :: Double -> AlphaColour Double -> PointStyle
- hollowCircles :: Double -> Double -> AlphaColour Double -> PointStyle
- filledPolygon :: Double -> Int -> Bool -> AlphaColour Double -> PointStyle
- hollowPolygon :: Double -> Double -> Int -> Bool -> AlphaColour Double -> PointStyle
- plusses :: Double -> Double -> AlphaColour Double -> PointStyle
- exes :: Double -> Double -> AlphaColour Double -> PointStyle
- stars :: Double -> Double -> AlphaColour Double -> PointStyle
- solidFillStyle :: AlphaColour Double -> FillStyle
- module Graphics.Rendering.Chart.Backend
- point_color :: Lens' PointStyle (AlphaColour Double)
- point_border_color :: Lens' PointStyle (AlphaColour Double)
- point_border_width :: Lens' PointStyle Double
- point_radius :: Lens' PointStyle Double
- point_shape :: Lens' PointStyle PointShape
Point Types and Drawing
data PointShape Source
The different shapes a point can have.
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. |
data PointStyle Source
Abstract data type for the style of a plotted point.
PointStyle | |
|
Default PointStyle | Default style to use for points. |
:: PointStyle | Style to use when rendering the point. |
-> Point | Position of the point to render. |
-> ChartBackend () |
Draw a single point at the given location.
defaultPointStyle :: PointStyleSource
Deprecated: Use the according Data.Default instance!
Default style for points.
Alignments and Paths
alignPath :: (Point -> Point) -> Path -> PathSource
Align the path by applying the given function on all points.
alignFillPath :: Path -> ChartBackend PathSource
Align the path using the environment's alignment function for coordinates.
This is generally useful when filling.
See alignPath
and getCoordAlignFn
.
alignStrokePath :: Path -> ChartBackend PathSource
Align the path using the environment's alignment function for points.
This is generally useful when stroking.
See alignPath
and getPointAlignFn
.
alignFillPoints :: [Point] -> ChartBackend [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] -> ChartBackend [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 -> ChartBackend PointSource
Align the point using the environment's alignment function for coordinates.
See getCoordAlignFn
.
alignStrokePoint :: Point -> ChartBackend PointSource
Align the point using the environment's alignment function for points.
See getPointAlignFn
.
strokePointPath :: [Point] -> ChartBackend ()Source
Draw lines between the specified points.
fillPointPath :: [Point] -> ChartBackend ()Source
Fill the region with the given corners.
Transformation and Style Helpers
withRotation :: Double -> ChartBackend a -> ChartBackend aSource
Apply a local rotation. The angle is given in radians.
withTranslation :: Point -> ChartBackend a -> ChartBackend aSource
Apply a local translation.
withScale :: Vector -> ChartBackend a -> ChartBackend aSource
Apply a local scale.
withScaleX :: Double -> ChartBackend a -> ChartBackend aSource
Apply a local scale on the x-axis.
withScaleY :: Double -> ChartBackend a -> ChartBackend aSource
Apply a local scale on the y-axis.
withPointStyle :: PointStyle -> ChartBackend a -> ChartBackend aSource
Changes the LineStyle
and FillStyle
to comply with
the given PointStyle
.
withDefaultStyle :: ChartBackend a -> ChartBackend aSource
Text Drawing
drawTextA :: HTextAnchor -> VTextAnchor -> Point -> String -> ChartBackend ()Source
Draw a line of text that is aligned at a different anchor point.
See drawText
.
drawTextR :: HTextAnchor -> VTextAnchor -> Double -> Point -> String -> ChartBackend ()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 -> ChartBackend ()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 -> ChartBackend RectSource
textDimension :: String -> ChartBackend RectSizeSource
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.
:: Double | Width of line. |
-> AlphaColour Double | Colour of line. |
-> LineStyle |
Create a solid line style (not dashed).
:: Double | Width of line. |
-> [Double] | The dash pattern in device coordinates. |
-> AlphaColour Double | Colour of line. |
-> LineStyle |
Create a dashed line style.
:: Double | Radius of circle. |
-> AlphaColour Double | Fill colour. |
-> PointStyle |
Style for filled circle points.
:: Double | Radius of circle. |
-> Double | Thickness of line. |
-> AlphaColour Double | |
-> PointStyle |
Style for stroked circle points.
:: Double | Radius of circle. |
-> Int | Number of vertices. |
-> Bool | Is right-side-up? |
-> AlphaColour Double | Fill color. |
-> PointStyle |
Style for filled polygon points.
:: 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.
:: Double | Radius of tightest surrounding circle. |
-> Double | Thickness of line. |
-> AlphaColour Double | Color of line. |
-> PointStyle |
Plus sign point style.
:: Double | Radius of circle. |
-> Double | Thickness of line. |
-> AlphaColour Double | Color of line. |
-> PointStyle |
Cross point style.
:: Double | Radius of circle. |
-> Double | Thickness of line. |
-> AlphaColour Double | Color of line. |
-> PointStyle |
Combination of plus and cross point style.
solidFillStyle :: AlphaColour Double -> FillStyleSource
Fill style that fill everything this the given colour.