Graphics.Rendering.Chart.Types
Description
This module contains basic types and functions used for drawing.
Note that template haskell is used to derive accessor functions
(see Data.Accessor
) 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 :: Data.Accessor.Accessor D F
- data Rect = Rect Point Point
- data Point = Point {}
- data Vector = Vector {}
- type RectSize = (Double, Double)
- type Range = (Double, Double)
- mkrect :: Point -> Point -> Point -> Point -> Rect
- pvadd :: Point -> Vector -> Point
- pvsub :: Point -> Vector -> Point
- psub :: Point -> Point -> Vector
- vscale :: Double -> Vector -> Vector
- within :: Point -> Rect -> Bool
- data RectEdge
- data Limit a
- type PointMapFn x y = (Limit x, Limit y) -> Point
- preserveCState :: CRender a -> CRender a
- setClipRegion :: Point -> Point -> CRender ()
- moveTo, lineTo :: Point -> CRender ()
- rectPath :: Rect -> [Point]
- strokePath :: [Point] -> CRender ()
- fillPath :: [Point] -> CRender ()
- isValidNumber :: RealFloat a => a -> Bool
- maybeM :: Monad m => b -> (a -> m b) -> Maybe a -> m b
- defaultColorSeq :: [AlphaColour Double]
- setSourceColor :: AlphaColour Double -> Render ()
- data CairoLineStyle = CairoLineStyle {}
- solidLine :: Double -> AlphaColour Double -> CairoLineStyle
- dashedLine :: Double -> [Double] -> AlphaColour Double -> CairoLineStyle
- setLineStyle :: CairoLineStyle -> CRender ()
- newtype CairoFillStyle = CairoFillStyle (CRender ())
- defaultPointStyle :: CairoPointStyle
- solidFillStyle :: AlphaColour Double -> CairoFillStyle
- setFillStyle :: CairoFillStyle -> CRender ()
- data CairoFontStyle = CairoFontStyle {}
- defaultFontStyle :: CairoFontStyle
- setFontStyle :: CairoFontStyle -> CRender ()
- newtype CairoPointStyle = CairoPointStyle (Point -> CRender ())
- filledPolygon :: Double -> Int -> Bool -> AlphaColour Double -> CairoPointStyle
- hollowPolygon :: Double -> Double -> Int -> Bool -> AlphaColour Double -> CairoPointStyle
- filledCircles :: Double -> AlphaColour Double -> CairoPointStyle
- hollowCircles :: Double -> Double -> AlphaColour Double -> CairoPointStyle
- plusses :: Double -> Double -> AlphaColour Double -> CairoPointStyle
- exes :: Double -> Double -> AlphaColour Double -> CairoPointStyle
- stars :: Double -> Double -> AlphaColour Double -> CairoPointStyle
- data HTextAnchor
- = HTA_Left
- | HTA_Centre
- | HTA_Right
- data VTextAnchor
- = VTA_Top
- | VTA_Centre
- | VTA_Bottom
- | VTA_BaseLine
- drawText :: HTextAnchor -> VTextAnchor -> Point -> String -> CRender ()
- drawTextR :: HTextAnchor -> VTextAnchor -> Double -> Point -> String -> CRender ()
- drawTextsR :: HTextAnchor -> VTextAnchor -> Double -> Point -> String -> CRender ()
- textSize :: String -> CRender RectSize
- textDrawRect :: HTextAnchor -> VTextAnchor -> Point -> String -> CRender Rect
- newtype CRender a = DR (ReaderT CEnv Render a)
- data CEnv = CEnv {
- cenv_point_alignfn :: Point -> Point
- cenv_coord_alignfn :: Point -> Point
- runCRender :: CRender a -> CEnv -> Render a
- c :: Render a -> CRender a
- alignp :: Point -> CRender Point
- alignc :: Point -> CRender Point
- line_width :: T CairoLineStyle Double
- line_color :: T CairoLineStyle (AlphaColour Double)
- line_dashes :: T CairoLineStyle [Double]
- line_cap :: T CairoLineStyle LineCap
- line_join :: T CairoLineStyle LineJoin
- font_name :: T CairoFontStyle String
- font_size :: T CairoFontStyle Double
- font_slant :: T CairoFontStyle FontSlant
- font_weight :: T CairoFontStyle FontWeight
- font_color :: T CairoFontStyle (AlphaColour Double)
Documentation
A rectangle is defined by two points.
A point in two dimensions.
mkrect :: Point -> Point -> Point -> Point -> RectSource
Create a rectangle based upon the coordinates of 4 points.
type PointMapFn x y = (Limit x, Limit y) -> PointSource
A function mapping between points.
preserveCState :: CRender a -> CRender aSource
Execute a rendering action in a saved context (ie bracketed between C.save and C.restore).
strokePath :: [Point] -> CRender ()Source
Draw lines between the specified points.
The points will be corrected by the cenv_point_alignfn, so that when drawing bitmaps, 1 pixel wide lines will be centred on the pixels.
fillPath :: [Point] -> CRender ()Source
Fill the region with the given corners.
The points will be corrected by the cenv_coord_alignfn, so that when drawing bitmaps, the edges of the region will fall between pixels.
isValidNumber :: RealFloat a => a -> BoolSource
data CairoLineStyle Source
Data type for the style of a line.
Constructors
CairoLineStyle | |
Fields
|
Arguments
:: Double | Width of line. |
-> AlphaColour Double | |
-> CairoLineStyle |
Arguments
:: Double | Width of line. |
-> [Double] | The dash pattern in device coordinates. |
-> AlphaColour Double | |
-> CairoLineStyle |
newtype CairoFillStyle Source
Abstract data type for a fill style.
The contained Cairo action sets the required fill style in the Cairo rendering state.
Constructors
CairoFillStyle (CRender ()) |
newtype CairoPointStyle Source
Abstract data type for the style of a plotted point.
The contained Cairo action draws a point in the desired style, at the supplied device coordinates.
Constructors
CairoPointStyle (Point -> CRender ()) |
Arguments
:: Double | Radius of circle. |
-> Int | Number of vertices. |
-> Bool | Is right-side-up? |
-> AlphaColour Double | |
-> CairoPointStyle |
Arguments
:: Double | Radius of circle. |
-> Double | Thickness of line. |
-> Int | Number of vertices. |
-> Bool | Is right-side-up? |
-> AlphaColour Double | |
-> CairoPointStyle |
Arguments
:: Double | Radius of circle. |
-> AlphaColour Double | Colour. |
-> CairoPointStyle |
Arguments
:: Double | Radius of circle. |
-> Double | Thickness of line. |
-> AlphaColour Double | |
-> CairoPointStyle |
Arguments
:: Double | Radius of circle. |
-> Double | Thickness of line. |
-> AlphaColour Double | |
-> CairoPointStyle |
Arguments
:: Double | Radius of circle. |
-> Double | Thickness of line. |
-> AlphaColour Double | |
-> CairoPointStyle |
Arguments
:: Double | Radius of circle. |
-> Double | Thickness of line. |
-> AlphaColour Double | |
-> CairoPointStyle |
data HTextAnchor Source
Constructors
HTA_Left | |
HTA_Centre | |
HTA_Right |
data VTextAnchor Source
Constructors
VTA_Top | |
VTA_Centre | |
VTA_Bottom | |
VTA_BaseLine |
drawText :: HTextAnchor -> VTextAnchor -> Point -> String -> CRender ()Source
Function to draw a textual label anchored by one of its corners or edges.
drawTextR :: HTextAnchor -> VTextAnchor -> Double -> Point -> String -> CRender ()Source
Function to 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.
drawTextsR :: HTextAnchor -> VTextAnchor -> Double -> Point -> String -> CRender ()Source
Function to 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.
textSize :: String -> CRender RectSizeSource
Return the bounding rectangle for a text string rendered in the current context.
textDrawRect :: HTextAnchor -> VTextAnchor -> Point -> String -> CRender RectSource
Recturn the bounding rectangle for a text string positioned where it would be drawn by drawText
The reader monad containing context information to control the rendering process.
The environment present in the CRender Monad.
Constructors
CEnv | |
Fields
|
Instances
runCRender :: CRender a -> CEnv -> Render aSource