cairo-0.13.4.1: Binding to the Cairo library.

Copyright(c) Paolo Martini 2005 (c) Abraham Egnor 2004 (c) Aetion Technologies LLC 2004
LicenseBSD-style (see cairo/COPYRIGHT)
Maintainerp.martini@neuralnoise.com
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell98

Graphics.Rendering.Cairo

Contents

Description

The Cairo 2D graphics library.

Cairo is a 2D graphics library with support for multiple output devices. Currently supported output targets include the X Window System, win32, and image buffers. Experimental backends include OpenGL (through glitz), Quartz, XCB, PostScript and PDF file output.

Cairo is designed to produce consistent output on all output media while taking advantage of display hardware acceleration when available (eg. through the X Render Extension).

The cairo API provides operations similar to the drawing operators of PostScript and PDF. Operations in cairo including stroking and filling cubic Bezier splines, transforming and compositing translucent images, and antialiased text rendering. All drawing operations can be transformed by any affine transformation (scale, rotation, shear, etc.)

Cairo is free software and is available to be redistributed and/or modified under the terms of either the GNU Lesser General Public License (LGPL) version 2.1 or the Mozilla Public License (MPL) version 1.1.

For more information see http://cairographics.org

  • Note the Haskell bindings do not support all the possible cairo backends because it would require bindings for the associated technology (eg X11, glitz, etc) however bindings to other backends may be implemented externally. For example, Gtk2Hs provides a binding to the backend for X11 (and win32 on Windows).

Synopsis

Drawing

renderWith Source #

Arguments

:: MonadIO m 
=> Surface

the target surface for the Render context

-> Render a 
-> m a 

Creates a new Render context with all graphics state parameters set to default values and with the given surface as a target surface. The target surface should be constructed with a backend-specific function such as withImageSurface (or any other with<backend>Surface variant).

save :: Render () Source #

Makes a copy of the current state and saves it on an internal stack of saved states. When restore is called, the saved state is restored. Multiple calls to save and restore can be nested; each call to restore restores the state from the matching paired save.

restore :: Render () Source #

Restores to the state saved by a preceding call to save and removes that state from the stack of saved states.

status :: Render Status Source #

Ask for the status of the current Render monad.

withTargetSurface :: (Surface -> Render a) -> Render a Source #

Gets the target surface for the Render context as passed to renderWith.

pushGroup :: Render () Source #

Like pushGroupWithContent ContentColorAlpha, but more convenient.

pushGroupWithContent :: Content -> Render () Source #

Temporarily redirects drawing to an intermediate surface known as a group. The redirection lasts until the group is completed by a call to withGroupPattern or popGroupToSource. These calls provide the result of any drawing to the group as a pattern (either as an explicit object, or set as the source pattern). This group functionality can be convenient for performing intermediate compositing. One common use of a group is to render objects as opaque within the group (so that they occlude each other), and then blend the result with translucence onto the destination.

Groups can be nested arbitrarily deeply by making balanced calls to pushGroupWithContent and withGroupPattern. As a side effect, pushGroupWithContent calls save and withGroupPattern calls restore, so that any changes to the graphics state will not be visible outside the group.

As an example, here is how one might fill and stroke a path with translucence, but without any portion of the fill being visible under the stroke:

pushGroup
setSource fillPattern
fillPreserve
setSource strokePattern
stroke
popGroupToSource
paintWithAlpha alpha

popGroupToSource :: Render () Source #

Like withGroupPattern setSource, but more convenient.

setSourceRGB Source #

Arguments

:: Double

red component of colour

-> Double

green component of colour

-> Double

blue compoment of colour

-> Render () 

Sets the source pattern within the context to an opaque color. This opaque color will then be used for any subsequent drawing operation until a new source pattern is set.

The color components are floating point numbers in the range 0 to 1. If the values passed in are outside that range, they will be clamped.

setSourceRGBA Source #

Arguments

:: Double

red component of color

-> Double

green component of color

-> Double

blue component of color

-> Double

alpha component of color

-> Render () 

Sets the source pattern within the context to a translucent color. This color will then be used for any subsequent drawing operation until a new source pattern is set.

The color and alpha components are floating point numbers in the range 0 to 1. If the values passed in are outside that range, they will be clamped.

setSource Source #

Arguments

:: Pattern

a Pattern to be used as the source for subsequent drawing operations.

-> Render () 

Sets the source pattern within the context to source. This pattern will then be used for any subsequent drawing operation until a new source pattern is set.

Note: The pattern's transformation matrix will be locked to the user space in effect at the time of setSource. This means that further modifications of the current transformation matrix will not affect the source pattern. See setMatrix.

setSourceSurface Source #

Arguments

:: Surface

a surface to be used to set the source pattern

-> Double

user-space X coordinate for surface origin

-> Double

user-space Y coordinate for surface origin

-> Render () 

This is a convenience function for creating a pattern from surface and setting it as the source in the context with setSource.

The x and y parameters give the user-space coordinate at which the surface origin should appear. (The surface origin is its upper-left corner before any transformation has been applied.) The x and y patterns are negated and then set as translation values in the pattern matrix.

Other than the initial translation pattern matrix, as described above, all other pattern attributes, (such as its extend mode), are set to the default values as in patternCreateForSurface. The resulting pattern can be queried with getSource so that these attributes can be modified if desired, (eg. to create a repeating pattern with patternSetExtent.

getSource :: Render Pattern Source #

Gets the current source pattern.

setAntialias Source #

Arguments

:: Antialias

the new antialiasing mode

-> Render () 

Set the antialiasing mode of the rasterizer used for drawing shapes. This value is a hint, and a particular backend may or may not support a particular value. At the current time, no backend supports AntialiasSubpixel when drawing shapes.

Note that this option does not affect text rendering, instead see fontOptionsSetAntilias.

setDash Source #

Arguments

:: [Double]

dashes a list specifying alternate lengths of on and off portions of the stroke

-> Double

an offset into the dash pattern at which the stroke should start

-> Render () 

Sets the dash pattern to be used by stroke. A dash pattern is specified by dashes, a list of positive values. Each value provides the user-space length of altenate "on" and "off" portions of the stroke. The offset specifies an offset into the pattern at which the stroke begins.

If dashes is [] then dashing is disabled.

setFillRule Source #

Arguments

:: FillRule

a fill rule

-> Render () 

Set the current fill rule within the cairo context. The fill rule is used to determine which regions are inside or outside a complex (potentially self-intersecting) path. The current fill rule affects both fill and clip. See FillRule for details on the semantics of each available fill rule.

getFillRule :: Render FillRule Source #

Gets the current fill rule, as set by setFillrule.

setLineCap Source #

Arguments

:: LineCap

a line cap style

-> Render () 

Sets the current line cap style within the cairo context. See LineCap for details about how the available line cap styles are drawn.

As with the other stroke parameters, the current line cap style is examined by stroke, strokeExtents, and strokeToPath, but does not have any effect during path construction.

getLineCap :: Render LineCap Source #

Gets the current line cap style, as set by setLineCap.

setLineJoin Source #

Arguments

:: LineJoin

a line joint style

-> Render () 

Sets the current line join style within the cairo context. See LineJoin for details about how the available line join styles are drawn.

As with the other stroke parameters, the current line join style is examined by stroke, strokeExtents, and strokeToPath, but does not have any effect during path construction.

getLineJoin :: Render LineJoin Source #

Gets the current line join style, as set by setLineJoin.

setLineWidth Source #

Arguments

:: Double

a line width

-> Render () 

Sets the current line width within the cairo context. The line width specifies the diameter of a pen that is circular in user-space.

As with the other stroke parameters, the current line cap style is examined by stroke, strokeExtents, and strokeToPath, but does not have any effect during path construction.

getLineWidth :: Render Double Source #

Gets the current line width, as set by setLineWidth.

setMiterLimit Source #

Arguments

:: Double
-> Render () 

getMiterLimit :: Render Double Source #

Gets the current miter limit, as set by setMiterLimit.

setOperator Source #

Arguments

:: Operator

a compositing operator

-> Render () 

Sets the compositing operator to be used for all drawing operations. See Operator for details on the semantics of each available compositing operator.

getOperator :: Render Operator Source #

Gets the current compositing operator for a cairo context.

setTolerance Source #

Arguments

:: Double

the tolerance, in device units (typically pixels)

-> Render () 

Sets the tolerance used when converting paths into trapezoids. Curved segments of the path will be subdivided until the maximum deviation between the original path and the polygonal approximation is less than tolerance. The default value is 0.1. A larger value will give better performance, a smaller value, better appearance. (Reducing the value from the default value of 0.1 is unlikely to improve appearance significantly.)

getTolerance :: Render Double Source #

Gets the current tolerance value, as set by setTolerance.

clip :: Render () Source #

Establishes a new clip region by intersecting the current clip region with the current path as it would be filled by fill and according to the current fill rule (see setFillRule).

After clip, the current path will be cleared from the cairo context.

The current clip region affects all drawing operations by effectively masking out any changes to the surface that are outside the current clip region.

Calling clip can only make the clip region smaller, never larger. But the current clip is part of the graphics state, so a temporary restriction of the clip region can be achieved by calling clip within a 'save'/'restore' pair. The only other means of increasing the size of the clip region is resetClip.

clipPreserve :: Render () Source #

Establishes a new clip region by intersecting the current clip region with the current path as it would be filled by fill and according to the current fill rule (see setFillRule).

Unlike clip, cairoClipPreserve preserves the path within the cairo context.

The current clip region affects all drawing operations by effectively masking out any changes to the surface that are outside the current clip region.

Calling clip can only make the clip region smaller, never larger. But the current clip is part of the graphics state, so a temporary restriction of the clip region can be achieved by calling clip within a 'save'/'restore' pair. The only other means of increasing the size of the clip region is resetClip.

clipExtents :: Render (Double, Double, Double, Double) Source #

Computes a bounding box in user coordinates covering the area inside the current clip.

resetClip :: Render () Source #

Reset the current clip region to its original, unrestricted state. That is, set the clip region to an infinitely large shape containing the target surface. Equivalently, if infinity is too hard to grasp, one can imagine the clip region being reset to the exact bounds of the target surface.

Note that code meant to be reusable should not call resetClip as it will cause results unexpected by higher-level code which calls clip. Consider using save and restore around clip as a more robust means of temporarily restricting the clip region.

fill :: Render () Source #

A drawing operator that fills the current path according to the current fill rule, (each sub-path is implicitly closed before being filled). After fill, the current path will be cleared from the cairo context.

See setFillRule and fillPreserve.

fillPreserve :: Render () Source #

A drawing operator that fills the current path according to the current fill rule, (each sub-path is implicitly closed before being filled). Unlike fill, fillPreserve preserves the path within the cairo context.

See setFillRule and fill.

mask Source #

Arguments

:: Pattern

a Pattern

-> Render () 

A drawing operator that paints the current source using the alpha channel of pattern as a mask. (Opaque areas of mask are painted with the source, transparent areas are not painted.)

maskSurface Source #

Arguments

:: Surface

a Surface

-> Double

X coordinate at which to place the origin of surface

-> Double

Y coordinate at which to place the origin of surface

-> Render () 

A drawing operator that paints the current source using the alpha channel of surface as a mask. (Opaque areas of surface are painted with the source, transparent areas are not painted.)

paint :: Render () Source #

A drawing operator that paints the current source everywhere within the current clip region.

paintWithAlpha Source #

Arguments

:: Double

alpha value, between 0 (transparent) and 1 (opaque)

-> Render () 

A drawing operator that paints the current source everywhere within the current clip region using a mask of constant alpha value alpha. The effect is similar to paint, but the drawing is faded out using the alpha value.

stroke :: Render () Source #

A drawing operator that strokes the current path according to the current line width, line join, line cap, and dash settings. After issuing stroke, the current path will be cleared from the Render monad.

See setLineWidth, setLineJoin, setLineCap, setDash, and strokePreserve.

strokePreserve :: Render () Source #

A drawing operator that strokes the current path according to the current line width, line join, line cap, and dash settings. Unlike stroke, strokePreserve preserves the path within the Render monad.

See setLineWidth, setLineJoin, setLineCap, setDash, and strokePreserve.

Paths

getCurrentPoint :: Render (Double, Double) Source #

Gets the current point of the current path, which is conceptually the final point reached by the path so far.

The current point is returned in the user-space coordinate system. If there is no defined current point then x and y will both be set to 0.0.

Most path construction functions alter the current point. See the following for details on how they affect the current point: newPath, moveTo, lineTo, curveTo, arc, relMoveTo, relLineTo, relCurveTo, arcNegative, textPath, strokeToPath.

newPath :: Render () Source #

Clears the current path. After this call there will be no current point.

closePath :: Render () Source #

Adds a line segment to the path from the current point to the beginning of the current subpath, (the most recent point passed to moveTo), and closes this subpath.

The behavior of closePath is distinct from simply calling lineTo with the equivalent coordinate in the case of stroking. When a closed subpath is stroked, there are no caps on the ends of the subpath. Instead, their is a line join connecting the final and initial segments of the subpath.

arc Source #

Arguments

:: Double

xc - X position of the center of the arc

-> Double

yc - Y position of the center of the arc

-> Double

radius - the radius of the arc

-> Double

angle1 - the start angle, in radians

-> Double

angle2 - the end angle, in radians

-> Render () 

Adds a circular arc of the given radius to the current path. The arc is centered at (xc, yc), begins at angle1 and proceeds in the direction of increasing angles to end at angle2. If angle2 is less than angle1 it will be progressively increased by 2*pi until it is greater than angle1.

If there is a current point, an initial line segment will be added to the path to connect the current point to the beginning of the arc.

Angles are measured in radians. An angle of 0 is in the direction of the positive X axis (in user-space). An angle of pi/2 radians (90 degrees) is in the direction of the positive Y axis (in user-space). Angles increase in the direction from the positive X axis toward the positive Y axis. So with the default transformation matrix, angles increase in a clockwise direction.

(To convert from degrees to radians, use degrees * (pi / 180).)

This function gives the arc in the direction of increasing angles; see arcNegative to get the arc in the direction of decreasing angles.

The arc is circular in user-space. To achieve an elliptical arc, you can scale the current transformation matrix by different amounts in the X and Y directions. For example, to draw an ellipse in the box given by x, y, width, height:

save
translate (x + width / 2) (y + height / 2)
scale (1 / (height / 2.)) (1 / (width / 2))
arc 0 0 1 0 (2 * pi)
restore

arcNegative Source #

Arguments

:: Double

xc - X position of the center of the arc

-> Double

yc - Y position of the center of the arc

-> Double

radius - the radius of the arc

-> Double

angle1 - the start angle, in radians

-> Double

angle2 - the end angle, in radians

-> Render () 

Adds a circular arc of the given radius to the current path. The arc is centered at (xc, yc), begins at angle1 and proceeds in the direction of decreasing angles to end at angle2. If angle2 is greater than angle1 it will be progressively decreased by 2*pi until it is greater than angle1.

See arc for more details. This function differs only in the direction of the arc between the two angles.

curveTo Source #

Arguments

:: Double

x1 - the X coordinate of the first control point

-> Double

y1 - the Y coordinate of the first control point

-> Double

x2 - the X coordinate of the second control point

-> Double

y2 - the Y coordinate of the second control point

-> Double

x3 - the X coordinate of the end of the curve

-> Double

y3 - the Y coordinate of the end of the curve

-> Render () 

Adds a cubic Bezier spline to the path from the current point to position (x3, y3) in user-space coordinates, using (x1, y1) and (x2, y2) as the control points. After this call the current point will be (x3, y3).

lineTo Source #

Arguments

:: Double

x - the X coordinate of the end of the new line

-> Double

y - the Y coordinate of the end of the new line

-> Render () 

Adds a line to the path from the current point to position (x, y) in user-space coordinates. After this call the current point will be (x, y).

moveTo Source #

Arguments

:: Double

x - the X coordinate of the new position

-> Double

y - the Y coordinate of the new position

-> Render () 

If the current subpath is not empty, begin a new subpath. After this call the current point will be (x, y).

rectangle Source #

Arguments

:: Double

x - the X coordinate of the top left corner of the rectangle

-> Double

y - the Y coordinate of the top left corner of the rectangle

-> Double

width - the width of the rectangle

-> Double

height - the height of the rectangle

-> Render () 

Adds a closed-subpath rectangle of the given size to the current path at position (x, y) in user-space coordinates.

textPath Source #

Arguments

:: CairoString string 
=> string
-> Render () 

Render text at the current path.

  • See showText for why you should use Gtk functions.

relCurveTo Source #

Arguments

:: Double

dx1 - the X offset to the first control point

-> Double

dy1 - the Y offset to the first control point

-> Double

dx2 - the X offset to the second control point

-> Double

dy2 - the Y offset to the second control point

-> Double

dx3 - the X offset to the end of the curve

-> Double

dy3 - the Y offset to the end of the curve

-> Render () 

Relative-coordinate version of curveTo. All offsets are relative to the current point. Adds a cubic Bezier spline to the path from the current point to a point offset from the current point by (dx3, dy3), using points offset by (dx1, dy1) and (dx2, dy2) as the control points. After this call the current point will be offset by (dx3, dy3).

Given a current point of (x, y), relCurveTo dx1 dy1 dx2 dy2 dx3 dy3 is logically equivalent to curveTo (x + dx1) (y + dy1) (x + dx2) (y + dy2) (x + dx3) (y + dy3).

relLineTo Source #

Arguments

:: Double

dx - the X offset to the end of the new line

-> Double

dy - the Y offset to the end of the new line

-> Render () 

Relative-coordinate version of lineTo. Adds a line to the path from the current point to a point that is offset from the current point by (dx, dy) in user space. After this call the current point will be offset by (dx, dy).

Given a current point of (x, y), relLineTo dx dy is logically equivalent to lineTo (x + dx) (y + dy).

relMoveTo Source #

Arguments

:: Double

dx - the X offset

-> Double

dy - the Y offset

-> Render () 

If the current subpath is not empty, begin a new subpath. After this call the current point will offset by (x, y).

Given a current point of (x, y), relMoveTo dx dy is logically equivalent to moveTo (x + dx) (y + dy)

Patterns

withRGBPattern Source #

Arguments

:: Double

red component of the color

-> Double

green component of the color

-> Double

blue component of the color

-> (Pattern -> Render a)

a nested render action using the pattern

-> Render a 

Creates a new Pattern corresponding to an opaque color. The color components are floating point numbers in the range 0 to 1. If the values passed in are outside that range, they will be clamped.

For example to create a solid red pattern:

withRBGPattern 1 0 0 $ do
  ...
  ...

withRGBAPattern Source #

Arguments

:: Double

red component of color

-> Double

green component of color

-> Double

blue component of color

-> Double

alpha component of color

-> (Pattern -> Render a)

a nested render action using the pattern

-> Render a 

Creates a new Pattern corresponding to a translucent color. The color components are floating point numbers in the range 0 to 1. If the values passed in are outside that range, they will be clamped.

For example to create a solid red pattern at 50% transparency:

withRBGPattern 1 0 0 0.5 $ do
  ...
  ...

withPatternForSurface Source #

Arguments

:: Surface 
-> (Pattern -> Render a)

a nested render action using the pattern

-> Render a 

Create a new Pattern for the given surface.

withGroupPattern Source #

Arguments

:: (Pattern -> Render a)

a nested render action using the pattern

-> Render a 

Pop the current group from the group stack and use it as a pattern. The group should be populated first by calling pushGroup or pushGroupWithContent and doing some drawing operations. This also calls restore to balance the save called in pushGroup.

withLinearPattern Source #

Arguments

:: Double

x0 - x coordinate of the start point

-> Double

y0 - y coordinate of the start point

-> Double

x1 - x coordinate of the end point

-> Double

y1 - y coordinate of the end point

-> (Pattern -> Render a)

a nested render action using the pattern

-> Render a 

Create a new linear gradient Pattern along the line defined by (x0, y0) and (x1, y1). Before using the gradient pattern, a number of color stops should be defined using patternAddColorStopRGB and patternAddColorStopRGBA.

  • Note: The coordinates here are in pattern space. For a new pattern, pattern space is identical to user space, but the relationship between the spaces can be changed with patternSetMatrix.

withRadialPattern Source #

Arguments

:: Double

cx0 - x coordinate for the center of the start circle

-> Double

cy0 - y coordinate for the center of the start circle

-> Double

radius0 - radius of the start cirle

-> Double

cx1 - x coordinate for the center of the end circle

-> Double

cy1 - y coordinate for the center of the end circle

-> Double

radius1 - radius of the end circle

-> (Pattern -> Render a)

a nested render action using the pattern

-> Render a 

Creates a new radial gradient Pattern between the two circles defined by (x0, y0, c0) and (x1, y1, c0). Before using the gradient pattern, a number of color stops should be defined using patternAddColorStopRGB or patternAddColorStopRGBA.

  • Note: The coordinates here are in pattern space. For a new pattern, pattern space is identical to user space, but the relationship between the spaces can be changed with patternSetMatrix.

patternAddColorStopRGB Source #

Arguments

:: MonadIO m 
=> Pattern

a Pattern

-> Double

an offset in the range [0.0 .. 1.0]

-> Double

red component of color

-> Double

green component of color

-> Double

blue component of color

-> m () 

Adds an opaque color stop to a gradient pattern. The offset specifies the location along the gradient's control vector. For example, a linear gradient's control vector is from (x0,y0) to (x1,y1) while a radial gradient's control vector is from any point on the start circle to the corresponding point on the end circle.

The color is specified in the same way as in setSourceRGB.

Note: If the pattern is not a gradient pattern, (eg. a linear or radial pattern), then the pattern will be put into an error status with a status of StatusPatternTypeMismatch.

patternAddColorStopRGBA Source #

Arguments

:: MonadIO m 
=> Pattern

a Pattern

-> Double

an offset in the range [0.0 .. 1.0]

-> Double

red component of color

-> Double

green component of color

-> Double

blue component of color

-> Double

alpha component of color

-> m () 

Adds a translucent color stop to a gradient pattern. The offset specifies the location along the gradient's control vector. For example, a linear gradient's control vector is from (x0,y0) to (x1,y1) while a radial gradient's control vector is from any point on the start circle to the corresponding point on the end circle.

The color is specified in the same way as in setSourceRGBA.

Note: If the pattern is not a gradient pattern, (eg. a linear or radial pattern), then the pattern will be put into an error status with a status of StatusPatternTypeMismatch.

patternSetMatrix Source #

Arguments

:: MonadIO m 
=> Pattern

a Pattern

-> Matrix

a Matrix

-> m () 

Sets the pattern's transformation matrix to matrix. This matrix is a transformation from user space to pattern space.

When a pattern is first created it always has the identity matrix for its transformation matrix, which means that pattern space is initially identical to user space.

Important: Please note that the direction of this transformation matrix is from user space to pattern space. This means that if you imagine the flow from a pattern to user space (and on to device space), then coordinates in that flow will be transformed by the inverse of the pattern matrix.

Also, please note the discussion of the user-space locking semantics of setSource.

patternGetMatrix Source #

Arguments

:: MonadIO m 
=> Pattern

a Pattern

-> m Matrix 

Get the pattern's transformation matrix.

patternSetExtend Source #

Arguments

:: MonadIO m 
=> Pattern

a Pattern

-> Extend

an Extent

-> m () 

Transformations

translate Source #

Arguments

:: Double

tx - amount to translate in the X direction

-> Double

ty - amount to translate in the Y direction

-> Render () 

Modifies the current transformation matrix (CTM) by translating the user-space origin by (tx, ty). This offset is interpreted as a user-space coordinate according to the CTM in place before the new call to translate. In other words, the translation of the user-space origin takes place after any existing transformation.

scale Source #

Arguments

:: Double

sx - scale factor for the X dimension

-> Double

sy - scale factor for the Y dimension

-> Render () 

Modifies the current transformation matrix (CTM) by scaling the X and Y user-space axes by sx and sy respectively. The scaling of the axes takes place after any existing transformation of user space.

rotate Source #

Arguments

:: Double

angle - angle (in radians) by which the user-space axes will be rotated

-> Render () 

Modifies the current transformation matrix (CTM) by rotating the user-space axes by angle radians. The rotation of the axes takes places after any existing transformation of user space. The rotation direction for positive angles is from the positive X axis toward the positive Y axis.

transform Source #

Arguments

:: Matrix

matrix - a transformation to be applied to the user-space axes

-> Render () 

Modifies the current transformation matrix (CTM) by applying matrix as an additional transformation. The new transformation of user space takes place after any existing transformation.

setMatrix Source #

Arguments

:: Matrix

matrix - a transformation matrix from user space to device space

-> Render () 

Modifies the current transformation matrix (CTM) by setting it equal to matrix.

getMatrix :: Render Matrix Source #

Gets the current transformation matrix, as set by setMatrix.

identityMatrix :: Render () Source #

Resets the current transformation matrix (CTM) by setting it equal to the identity matrix. That is, the user-space and device-space axes will be aligned and one user-space unit will transform to one device-space unit.

userToDevice Source #

Arguments

:: Double

X value of coordinate

-> Double

Y value of coordinate

-> Render (Double, Double) 

Transform a coordinate from user space to device space by multiplying the given point by the current transformation matrix (CTM).

userToDeviceDistance Source #

Arguments

:: Double

dx - X component of a distance vector

-> Double

dy - Y component of a distance vector

-> Render (Double, Double) 

Transform a distance vector from user space to device space. This function is similar to userToDevice except that the translation components of the CTM will be ignored when transforming (dx,dy).

deviceToUser Source #

Arguments

:: Double

X value of coordinate

-> Double

Y value of coordinate

-> Render (Double, Double) 

Transform a coordinate from device space to user space by multiplying the given point by the inverse of the current transformation matrix (CTM).

deviceToUserDistance Source #

Arguments

:: Double

dx - X component of a distance vector

-> Double

dy - Y component of a distance vector

-> Render (Double, Double) 

Transform a distance vector from device space to user space. This function is similar to deviceToUser except that the translation components of the inverse CTM will be ignored when transforming (dx,dy).

Text

selectFontFace Source #

Arguments

:: CairoString string 
=> string

family - a font family name

-> FontSlant

slant - the slant for the font

-> FontWeight

weight - the weight of the font

-> Render () 

Selects a family and style of font from a simplified description as a family name, slant and weight. This function is meant to be used only for applications with simple font needs: Cairo doesn't provide for operations such as listing all available fonts on the system, and it is expected that most applications will need to use a more comprehensive font handling and text layout library in addition to cairo.

setFontSize Source #

Arguments

:: Double

size - the new font size, in user space units

-> Render () 

Sets the current font matrix to a scale by a factor of size, replacing any font matrix previously set with setFontSize or setFontMatrix. This results in a font size of size user space units. (More precisely, this matrix will result in the font's em-square being a size by size square in user space.)

setFontMatrix Source #

Arguments

:: Matrix

matrix - a Matrix describing a transform to be applied to the current font.

-> Render () 

Sets the current font matrix to matrix. The font matrix gives a transformation from the design space of the font (in this space, the em-square is 1 unit by 1 unit) to user space. Normally, a simple scale is used (see setFontSize), but a more complex font matrix can be used to shear the font or stretch it unequally along the two axes.

getFontMatrix :: Render Matrix Source #

Gets the current font matrix, as set by setFontMatrix

setFontOptions :: FontOptions -> Render () Source #

Sets a set of custom font rendering options. Rendering options are derived by merging these options with the options derived from underlying surface; if the value in options has a default value (like AntialiasDefault), then the value from the surface is used.

showText Source #

Arguments

:: CairoString string 
=> string

a string of text

-> Render () 

A drawing operator that generates the shape from a string of Unicode characters, rendered according to the current font face, font size (font matrix), and font options.

This function first computes a set of glyphs for the string of text. The first glyph is placed so that its origin is at the current point. The origin of each subsequent glyph is offset from that of the previous glyph by the advance values of the previous glyph.

After this call the current point is moved to the origin of where the next glyph would be placed in this same progression. That is, the current point will be at the origin of the final glyph offset by its advance values. This allows for easy display of a single logical string with multiple calls to showText.

NOTE: The showText function call is part of what the cairo designers call the "toy" text API. It is convenient for short demos and simple programs, but it is not expected to be adequate for the most serious of text-using applications.

fontExtents :: Render FontExtents Source #

Gets the font extents for the currently selected font.

textExtents Source #

Arguments

:: CairoString string 
=> string

a string of text

-> Render TextExtents 

Gets the extents for a string of text. The extents describe a user-space rectangle that encloses the "inked" portion of the text, (as it would be drawn by showText). Additionally, the textExtentsXadvance and textExtentsYadvance values indicate the amount by which the current point would be advanced by showText.

Note that whitespace characters do not directly contribute to the size of the rectangle (textExtentsWidth and textExtentsHeight). They do contribute indirectly by changing the position of non-whitespace characters. In particular, trailing whitespace characters are likely to not affect the size of the rectangle, though they will affect the textExtentsXadvance and textExtentsYadvance values.

Fonts

Font options

fontOptionsCreate :: MonadIO m => m FontOptions Source #

Allocates a new font options object with all options initialized to default values.

fontOptionsCopy Source #

Arguments

:: MonadIO m 
=> FontOptions
original
-> m FontOptions 

Allocates a new font options object copying the option values from original.

fontOptionsMerge Source #

Arguments

:: MonadIO m 
=> FontOptions
options
-> FontOptions
other
-> m () 

Merges non-default options from other into options, replacing existing values. This operation can be thought of as somewhat similar to compositing other onto options with the operation of OperationOver.

fontOptionsHash :: MonadIO m => FontOptions -> m Int Source #

Compute a hash for the font options object; this value will be useful when storing an object containing a FontOptions in a hash table.

fontOptionsEqual :: MonadIO m => FontOptions -> FontOptions -> m Bool Source #

Compares two font options objects for equality.

fontOptionsSetAntialias :: MonadIO m => FontOptions -> Antialias -> m () Source #

Sets the antiliasing mode for the font options object. This specifies the type of antialiasing to do when rendering text.

fontOptionsGetAntialias :: MonadIO m => FontOptions -> m Antialias Source #

Gets the antialising mode for the font options object.

fontOptionsSetSubpixelOrder :: MonadIO m => FontOptions -> SubpixelOrder -> m () Source #

Sets the subpixel order for the font options object. The subpixel order specifies the order of color elements within each pixel on the display device when rendering with an antialiasing mode of AntialiasSubpixel. See the documentation for SubpixelOrder for full details.

fontOptionsGetSubpixelOrder :: MonadIO m => FontOptions -> m SubpixelOrder Source #

Gets the subpixel order for the font options object. See the documentation for SubpixelOrder for full details.

fontOptionsSetHintStyle :: MonadIO m => FontOptions -> HintStyle -> m () Source #

Sets the hint style for font outlines for the font options object. This controls whether to fit font outlines to the pixel grid, and if so, whether to optimize for fidelity or contrast. See the documentation for HintStyle for full details.

fontOptionsGetHintStyle :: MonadIO m => FontOptions -> m HintStyle Source #

Gets the hint style for font outlines for the font options object. See the documentation for HintStyle for full details.

fontOptionsSetHintMetrics :: MonadIO m => FontOptions -> HintMetrics -> m () Source #

Sets the metrics hinting mode for the font options object. This controls whether metrics are quantized to integer values in device units. See the documentation for HintMetrics for full details.

fontOptionsGetHintMetrics :: MonadIO m => FontOptions -> m HintMetrics Source #

Gets the metrics hinting mode for the font options object. See the documentation for HintMetrics for full details.

Surfaces

withSimilarSurface Source #

Arguments

:: Surface

an existing surface used to select the backend of the new surface

-> Content

the content type for the new surface (color, color+alpha or alpha only)

-> Int

width of the new surface, (in device-space units)

-> Int

height of the new surface (in device-space units)

-> (Surface -> IO a) 
-> IO a 

Create a temporary surface that is as compatible as possible with an existing surface. The new surface will use the same backend as other unless that is not possible for some reason.

createSimilarSurface Source #

Arguments

:: Surface

an existing surface used to select the backend of the new surface

-> Content

the content type for the new surface (color, color+alpha or alpha only)

-> Int

width of the surface, in pixels

-> Int

height of the surface, in pixels

-> IO Surface 

Like withSimilarSurface but creates a Surface that is managed by the Haskell memory manager rather than only being temporaily allocated. This is more flexible and allows you to create surfaces that persist, which can be very useful, for example to cache static elements in an animation.

However you should be careful because surfaces can be expensive resources and the Haskell memory manager cannot guarantee when it will release them. You can manually release the resources used by a surface with surfaceFinish.

renderWithSimilarSurface Source #

Arguments

:: Content

the content type for the new surface (color, colour+alpha or alpha only)

-> Int

width of the new surface, (in device-space units)

-> Int

height of the new surface, (in device-space units)

-> (Surface -> Render a)

this action draws on the main surface, possibly making use of the temporary surface (which gets destroyed afterwards).

-> Render a 

Create a temporary surface that is compatible with the current target surface (like a combination of withTargetSurface and withSimilarSurface).

This is useful for drawing to a temporary surface and then compositing it into the main suface. For example, the following code draws to a temporary surface and then uses that as a mask:

renderWithSimilarSurface ContentAlpha 200 200 $ \tmpSurface -> do
  renderWith tmpSurface $ do
    ... -- draw onto the temporary surface

  -- use the temporary surface as a mask, filling it with the
  -- current source which in this example is transparent red.
  setSourceRGBA 1 0 0 0.5
  setOperator Operator{something} -- think of something clever to do
  maskSurface tmpSurface 0 0)

surfaceGetFontOptions :: Surface -> Render FontOptions Source #

Retrieves the default font rendering options for the surface. This allows display surfaces to report the correct subpixel order for rendering on them, print surfaces to disable hinting of metrics and so forth. The result can then be used with scaledFontCreate.

surfaceFinish :: MonadIO m => Surface -> m () Source #

This function finishes the surface and drops all references to external resources. For example, for the Xlib backend it means that cairo will no longer access the drawable, which can be freed. After calling surfaceFinish the only valid operations on a surface are getting and setting user data and referencing and destroying it. Further drawing to the surface will not affect the surface but will instead trigger a StatusSurfaceFinished error.

When the last call to surfaceDestroy decreases the reference count to zero, cairo will call surfaceFinish if it hasn't been called already, before freeing the resources associated with the surface.

surfaceFlush :: MonadIO m => Surface -> m () Source #

Do any pending drawing for the surface and also restore any temporary modification's cairo has made to the surface's state. This function must be called before switching from drawing on the surface with cairo to drawing on it directly with native APIs. If the surface doesn't support direct access, then this function does nothing.

surfaceMarkDirty :: MonadIO m => Surface -> m () Source #

Tells cairo that drawing has been done to surface using means other than cairo, and that cairo should reread any cached areas. Note that you must call surfaceFlush before doing such drawing.

surfaceMarkDirtyRectangle Source #

Arguments

:: MonadIO m 
=> Surface

a Surface

-> Int

X coordinate of dirty rectangle

-> Int

Y coordinate of dirty rectangle

-> Int

width of dirty rectangle

-> Int

height of dirty rectangle

-> m () 

Like surfaceMarkDirty, but drawing has been done only to the specified rectangle, so that cairo can retain cached contents for other parts of the surface.

surfaceSetDeviceOffset Source #

Arguments

:: MonadIO m 
=> Surface

a Surface

-> Double

the offset in the X direction, in device units

-> Double

the offset in the Y direction, in device units

-> m () 

Sets an offset that is added to the device coordinates determined by the CTM when drawing to surface. One use case for this function is when we want to create a Surface that redirects drawing for a portion of an onscreen surface to an offscreen surface in a way that is completely invisible to the user of the cairo API. Setting a transformation via translate isn't sufficient to do this, since functions like deviceToUser will expose the hidden offset.

Note that the offset only affects drawing to the surface, not using the surface in a surface pattern.

Image surfaces

withImageSurface Source #

Arguments

:: Format

format of pixels in the surface to create

-> Int

width of the surface, in pixels

-> Int

height of the surface, in pixels

-> (Surface -> IO a)

an action that may use the surface. The surface is only valid within in this action.

-> IO a 

Creates an image surface of the specified format and dimensions. The initial contents of the surface is undefined; you must explicitely clear the buffer, using, for example, rectangle and fill if you want it cleared.

withImageSurfaceForData Source #

Arguments

:: PixelData

pointer to pixel data

-> Format

format of pixels in the surface to create

-> Int

width of the surface, in pixels

-> Int

height of the surface, in pixels

-> Int

size of stride between rows in the surface to create

-> (Surface -> IO a)

an action that may use the surface. The surface is only valid within this action

-> IO a 

Like withImageSurface but creating a surface to target external data pointed to by PixelData.

formatStrideForWidth Source #

Arguments

:: Format

format of pixels in the surface to create

-> Int

width of the surface, in pixels

-> Int

the stride (number of bytes necessary to store one line) or -1 if the format is invalid or the width is too large

This function provides a stride value that will respect all alignment requirements of the accelerated image-rendering code within cairo.

createImageSurfaceForData Source #

Arguments

:: PixelData

pointer to pixel data

-> Format

format of pixels in the surface to create

-> Int

width of the surface, in pixels

-> Int

height of the surface, in pixels

-> Int

size of stride between rows in the surface to create

-> IO Surface 

Like createImageSurface but creating a surface to target external data pointed to by PixelData.

createImageSurface Source #

Arguments

:: Format

format of pixels in the surface to create

-> Int

width of the surface, in pixels

-> Int

height of the surface, in pixels

-> IO Surface 

Like withImageSurface but creates a Surface that is managed by the Haskell memory manager rather than only being temporaily allocated. This is more flexible and allows you to create surfaces that persist, which can be very useful, for example to cache static elements in an animation.

However you should be careful because surfaces can be expensive resources and the Haskell memory manager cannot guarantee when it will release them. You can manually release the resources used by a surface with surfaceFinish.

imageSurfaceGetWidth :: MonadIO m => Surface -> m Int Source #

Get the width of the image surface in pixels.

imageSurfaceGetHeight :: MonadIO m => Surface -> m Int Source #

Get the height of the image surface in pixels.

imageSurfaceGetFormat :: MonadIO m => Surface -> m Format Source #

Get the format of the surface.

imageSurfaceGetStride :: MonadIO m => Surface -> m Int Source #

Get the number of bytes from the start of one row to the start of the next. If the image data contains no padding, then this is equal to the pixel depth * the width.

imageSurfaceGetData :: Surface -> IO ByteString Source #

Return a ByteString of the image data for a surface. In order to remain safe the returned ByteString is a copy of the data. This is a little slower than returning a pointer into the image surface object itself, but much safer

data SurfaceData i e Source #

An array that stores the raw pixel data of an image Surface.

Instances

Storable e => MArray SurfaceData e IO Source #

SurfaceData is a mutable array.

Methods

getBounds :: Ix i => SurfaceData i e -> IO (i, i) #

getNumElements :: Ix i => SurfaceData i e -> IO Int

newArray :: Ix i => (i, i) -> e -> IO (SurfaceData i e) #

newArray_ :: Ix i => (i, i) -> IO (SurfaceData i e) #

unsafeNewArray_ :: Ix i => (i, i) -> IO (SurfaceData i e)

unsafeRead :: Ix i => SurfaceData i e -> Int -> IO e

unsafeWrite :: Ix i => SurfaceData i e -> Int -> e -> IO ()

imageSurfaceGetPixels :: Storable e => Surface -> IO (SurfaceData Int e) Source #

Retrieve the internal array of raw image data.

  • Image data in an image surface is stored in memory in uncompressed, packed format. Rows in the image are stored top to bottom, and in each row pixels are stored from left to right. There may be padding at the end of a row. The value returned by imageSurfaceGetStride indicates the number of bytes between rows.
  • The returned array is a flat representation of a three dimensional array: x-coordiante, y-coordinate and several channels for each color. The format depends on the Format of the surface:

FormatARGB32: each pixel is 32 bits with alpha in the upper 8 bits, followed by 8 bits for red, green and blue. Pre-multiplied alpha is used. (That is, 50% transparent red is 0x80800000, not 0x80ff0000.)

FormatRGB24: each pixel is 32 bits with the upper 8 bits being unused, followed by 8 bits for red, green and blue.

FormatA8: each pixel is 8 bits holding an alpha value

FormatA1: each pixel is one bit where pixels are packed into 32 bit quantities. The ordering depends on the endianes of the platform. On a big-endian machine, the first pixel is in the uppermost bit, on a little-endian machine the first pixel is in the least-significant bit.

  • To read or write a specific pixel (and assuming FormatARGB32 or FormatRGB24), use the formula: p = y * (rowstride div 4) + x for the pixel and force the array to have 32-bit words or integers.
  • Calling this function without explicitly giving it a type will often lead to a compiler error since the type parameter e is underspecified. If this happens the function can be explicitly typed: surData <- (imageSurfaceGetPixels pb :: IO (SurfaceData Int Word32))
  • If modifying an image through Haskell's array interface is not fast enough, it is possible to use unsafeRead and unsafeWrite which have the same type signatures as readArray and writeArray. Note that these are internal functions that might change with GHC.
  • After each write access to the array, you need to inform Cairo about the area that has changed using surfaceMarkDirty.
  • The function will return an error if the surface is not an image surface or if surfaceFinish has been called on the surface.

PNG support

withImageSurfaceFromPNG :: FilePath -> (Surface -> IO a) -> IO a Source #

Creates a new image surface and initializes the contents to the given PNG file.

surfaceWriteToPNG Source #

Arguments

:: Surface

a Surface

-> FilePath

filename - the name of a file to write to

-> IO () 

Writes the contents of surface to a new file filename as a PNG image.

PDF surfaces

withPDFSurface Source #

Arguments

:: FilePath

filename - a filename for the PS output (must be writable)

-> Double

width of the surface, in points (1 point == 1/72.0 inch)

-> Double

height of the surface, in points (1 point == 1/72.0 inch)

-> (Surface -> IO a)

an action that may use the surface. The surface is only valid within in this action.

-> IO a 

Creates a PostScript surface of the specified size in points to be written to filename.

Note that the size of individual pages of the PostScript output can vary. See psSurfaceSetSize.

pdfSurfaceSetSize :: MonadIO m => Surface -> Double -> Double -> m () Source #

Changes the size of a PDF surface for the current (and subsequent) pages.

This function should only be called before any drawing operations have been performed on the current page. The simplest way to do this is to call this function immediately after creating the surface or immediately after completing a page with either showPage or copyPage.

PS surfaces

withPSSurface Source #

Arguments

:: FilePath

filename - a filename for the PS output (must be writable)

-> Double

width of the surface, in points (1 point == 1/72.0 inch)

-> Double

height of the surface, in points (1 point == 1/72.0 inch)

-> (Surface -> IO a)

an action that may use the surface. The surface is only valid within in this action.

-> IO a 

Creates a PostScript surface of the specified size in points to be written to filename.

Note that the size of individual pages of the PostScript output can vary. See psSurfaceSetSize.

psSurfaceSetSize :: MonadIO m => Surface -> Double -> Double -> m () Source #

Changes the size of a PostScript surface for the current (and subsequent) pages.

This function should only be called before any drawing operations have been performed on the current page. The simplest way to do this is to call this function immediately after creating the surface or immediately after completing a page with either showPage or copyPage.

SVG surfaces

withSVGSurface Source #

Arguments

:: FilePath

filename - a filename for the SVG output (must be writable)

-> Double

width of the surface, in points (1 point == 1/72.0 inch)

-> Double

height of the surface, in points (1 point == 1/72.0 inch)

-> (Surface -> IO a)

an action that may use the surface. The surface is only valid within in this action.

-> IO a 

Creates a SVG surface of the specified size in points be written to filename.

Regions

regionCreate :: MonadIO m => m Region Source #

Allocates a new empty region object.

regionCreateRectangle Source #

Arguments

:: MonadIO m 
=> RectangleInt
rectangle
-> m Region 

Allocates a new region object containing rectangle.

regionCreateRectangles Source #

Arguments

:: MonadIO m 
=> [RectangleInt]
rects
-> m Region 

Allocates a new region object containing the union of all given rects.

regionCopy Source #

Arguments

:: MonadIO m 
=> Region
original
-> m Region 

Allocates a new region object copying the area from original.

regionGetExtents Source #

Arguments

:: MonadIO m 
=> Region
region
-> m RectangleInt 

Gets the bounding rectangle of region as a RectanglInt.

regionNumRectangles Source #

Arguments

:: MonadIO m 
=> Region
region
-> m Int 

Returns the number of rectangles contained in region.

regionGetRectangle Source #

Arguments

:: MonadIO m 
=> Region
region
-> Int
nth
-> m RectangleInt 

Gets the nth rectangle from the region.

regionIsEmpty Source #

Arguments

:: MonadIO m 
=> Region
region
-> m Bool 

Checks whether region is empty.

regionContainsPoint Source #

Arguments

:: MonadIO m 
=> Region
region
-> Int
x
-> Int
y
-> m Bool 

Checks whether (x, y) is contained in region.

regionContainsRectangle Source #

Arguments

:: MonadIO m 
=> Region
region
-> RectangleInt
rectangle
-> m RegionOverlap 

Checks whether rectangle is inside, outside or partially contained in region.

regionEqual Source #

Arguments

:: MonadIO m 
=> Region
region_a
-> Region
region_b
-> m Bool 

Compares whether region_a is equivalent to region_b.

regionTranslate Source #

Arguments

:: MonadIO m 
=> Region
region
-> Int
dx
-> Int
dy
-> m () 

Translates region by (dx, dy).

regionIntersect Source #

Arguments

:: MonadIO m 
=> Region
dst
-> Region
other
-> m () 

Computes the intersection of dst with other and places the result in dst.

regionIntersectRectangle Source #

Arguments

:: MonadIO m 
=> Region
dst
-> RectangleInt
rectangle
-> m () 

Computes the intersection of dst with rectangle and places the result in dst.

regionSubtract Source #

Arguments

:: MonadIO m 
=> Region
dst
-> Region
other
-> m () 

Subtracts other from dst and places the result in dst.

regionSubtractRectangle Source #

Arguments

:: MonadIO m 
=> Region
dst
-> RectangleInt
rectangle
-> m () 

Subtracts rectangle from dst and places the result in dst.

regionUnion Source #

Arguments

:: MonadIO m 
=> Region
dst
-> Region
other
-> m () 

Computes the union of dst with other and places the result in dst.

regionUnionRectangle Source #

Arguments

:: MonadIO m 
=> Region
dst
-> RectangleInt
rectangle
-> m () 

Computes the union of dst with rectangle and places the result in dst.

regionXor Source #

Arguments

:: MonadIO m 
=> Region
dst
-> Region
other
-> m () 

Computes the exclusive difference of dst with other and places the result in dst. That is, dst will be set to contain all areas that are either in dst or in other, but not in both.

regionXorRectangle Source #

Arguments

:: MonadIO m 
=> Region
dst
-> RectangleInt
rectangle
-> m () 

Computes the exclusive difference of dst with rectangle and places the result in dst. That is, dst will be set to contain all areas that are either in dst or in rectangle, but not in both

Utilities

liftIO :: MonadIO m => forall a. IO a -> m a #

Lift a computation from the IO monad.

version :: Int Source #

Returns the version of the cairo library encoded in a single integer.

versionString :: String Source #

Returns the version of the cairo library as a human-readable string of the form "X.Y.Z".

class CairoString s Source #

Minimal complete definition

withUTFString

Instances

CairoString Text Source # 

Methods

withUTFString :: Text -> (CString -> IO a) -> IO a

CairoString [Char] Source # 

Methods

withUTFString :: [Char] -> (CString -> IO a) -> IO a

Types

data Render m Source #

The Render monad. All drawing operations take place in a Render context. You can obtain a Render context for a Surface using renderWith.

Instances

Monad Render Source # 

Methods

(>>=) :: Render a -> (a -> Render b) -> Render b #

(>>) :: Render a -> Render b -> Render b #

return :: a -> Render a #

fail :: String -> Render a #

Functor Render Source # 

Methods

fmap :: (a -> b) -> Render a -> Render b #

(<$) :: a -> Render b -> Render a #

Applicative Render Source # 

Methods

pure :: a -> Render a #

(<*>) :: Render (a -> b) -> Render a -> Render b #

(*>) :: Render a -> Render b -> Render b #

(<*) :: Render a -> Render b -> Render a #

MonadIO Render Source # 

Methods

liftIO :: IO a -> Render a #

data Matrix Source #

Representation of a 2-D affine transformation.

The Matrix type represents a 2x2 transformation matrix along with a translation vector. Matrix a1 a2 b1 b2 c1 c2 describes the transformation of a point with coordinates x,y that is defined by

  / x' \  =  / a1 b1 \  / x \  + / c1 \
  \ y' /     \ a2 b2 /  \ y /    \ c2 /

or

  x' =  a1 * x + b1 * y + c1
  y' =  a2 * x + b2 * y + c2

data Surface Source #

The medium to draw on.

data Pattern Source #

Patterns can be simple solid colors, various kinds of gradients or bitmaps. The current pattern for a Render context is used by the stroke, fill and paint operations. These operations composite the current pattern with the target surface using the currently selected Operator.

data Status Source #

Cairo status.

  • Status is used to indicate errors that can occur when using Cairo. In some cases it is returned directly by functions. When using Render, the last error, if any, is stored in the monad and can be retrieved with status.

data Antialias Source #

Specifies the type of antialiasing to do when rendering text or shapes

AntialiasDefault
Use the default antialiasing for the subsystem and target device.
AntialiasNone
Use a bilevel alpha mask.
AntialiasGray
Perform single-color antialiasing (using shades of gray for black text on a white background, for example).
AntialiasSubpixel
Perform antialiasing by taking advantage of the order of subpixel elements on devices such as LCD panels.

data FillRule Source #

Specify how paths are filled.

  • For both fill rules, whether or not a point is included in the fill is determined by taking a ray from that point to infinity and looking at intersections with the path. The ray can be in any direction, as long as it doesn't pass through the end point of a segment or have a tricky intersection such as intersecting tangent to the path. (Note that filling is not actually implemented in this way. This is just a description of the rule that is applied.)
FillRuleWinding
If the path crosses the ray from left-to-right, counts +1. If the path crosses the ray from right to left, counts -1. (Left and right are determined from the perspective of looking along the ray from the starting point.) If the total count is non-zero, the point will be filled.
FillRuleEvenOdd
Counts the total number of intersections, without regard to the orientation of the contour. If the total number of intersections is odd, the point will be filled.

data LineCap Source #

Specify line endings.

LineCapButt
Start(stop) the line exactly at the start(end) point.
LineCapRound
Use a round ending, the center of the circle is the end point.
LineCapSquare
Use squared ending, the center of the square is the end point

data SubpixelOrder Source #

The subpixel order specifies the order of color elements within each pixel on the display device when rendering with an antialiasing mode of AntialiasSubpixel.

SubpixelOrderDefault
Use the default subpixel order for for the target device
SubpixelOrderRgb
Subpixel elements are arranged horizontally with red at the left
SubpixelOrderBgr
Subpixel elements are arranged horizontally with blue at the left
SubpixelOrderVrgb
Subpixel elements are arranged vertically with red at the top
SubpixelOrderVbgr
Subpixel elements are arranged vertically with blue at the top

data HintStyle Source #

Specifies the type of hinting to do on font outlines.

Hinting is the process of fitting outlines to the pixel grid in order to improve the appearance of the result. Since hinting outlines involves distorting them, it also reduces the faithfulness to the original outline shapes. Not all of the outline hinting styles are supported by all font backends.

HintStyleDefault
Use the default hint style for for font backend and target device
HintStyleNone
Do not hint outlines
HintStyleSlight
Hint outlines slightly to improve contrast while retaining good fidelity to the original shapes.
HintStyleMedium
Hint outlines with medium strength giving a compromise between fidelity to the original shapes and contrast
HintStyleFull
Hint outlines to maximize contrast

data HintMetrics Source #

Specifies whether to hint font metrics.

Hinting font metrics means quantizing them so that they are integer values in device space. Doing this improves the consistency of letter and line spacing, however it also means that text will be laid out differently at different zoom factors.

HintMetricsDefault
Hint metrics in the default manner for the font backend and target device
HintMetricsOff
Do not hint font metrics
HintMetricsOn
Hint font metrics

data FontOptions Source #

Specifies how to render text.

data Path Source #

A Cairo path.

  • A path is a sequence of drawing operations that are accumulated until stroke is called. Using a path is particularly useful when drawing lines with special join styles and closePath.

data RectangleInt Source #

A data structure for holding a rectangle with integer coordinates.

Constructors

RectangleInt 

Fields

data Region Source #

A Cairo region. Represents a set of integer-aligned rectangles.

It allows set-theoretical operations like regionUnion and regionIntersect to be performed on them.

data Extend Source #

FIXME: We should find out about this.