curves-1.1.0.2: Library for drawing curve based images.

Safe HaskellNone
LanguageHaskell98

Graphics.Curves

Contents

Description

Curves is an easy to use library for creating images. The basic primitive is a curve, which, in the simplest case, is a continuous function from a Scalar parameter to a 2-dimensional Point on the curve. Images are rendered (renderImage) as PNG images.

Synopsis

Documentation

Image

Curves

point :: Point -> Image Source

A single point.

line :: Point -> Point -> Image Source

A straight line between two points.

lineStrip :: [Point] -> Image Source

A connected sequence of straight lines. The list must have at least two elements.

poly :: [Point] -> Image Source

A polygon.

poly ps = lineStrip (ps ++ [head ps])

circle :: Point -> Scalar -> Image Source

A circle given by its center and radius.

circleSegment :: Point -> Scalar -> Scalar -> Scalar -> Image Source

A circle segment. The third and fourth arguments are the start and end angle of the segment. If the start angle is bigger than the end angle it's the clockwise segment, otherwise the counterclockwise segment. For instance, circleSegment 0 1 0 pi is the top half circle starting in unitX and ending in -unitX, whereas circleSegment 0 1 0 (-pi) is the bottow half circle with the same start and end points.

Advanced curves

curve :: Scalar -> Scalar -> (Scalar -> Point) -> Image Source

A simple curve whose points are given by the function argument. The first two arguments specify the range of the function. The function must be continuous on this interval.

For example, a straight line between points p and q can be implemented as

curve 0 1 (interpolate p q)

curve_ :: (Scalar -> Point) -> Image Source

curve_ = curve 0 1

curve' :: Transformable a => Scalar -> Scalar -> (Scalar -> a) -> (Scalar -> a -> Point) -> Image Source

The most general form of curve. The curve function is split in two, one function from the parameter to an arbitrary Transformable object, and a second function from this object (and the parameter value) to a point on the curve. The power of this combinator comes from the fact that transformations (e.g. translate, scale, rotate) of the curve apply only to the (result of the) first function. This means that the points computed by the second function are measured in pixels of the final image.

For an example, see the arrow combinator, which uses a line Segment as the intermediate type and computes the arrow head in the second function, to ensure that the arrow head has the same dimensions regardless of how the arrow is scaled.

bSpline :: [Point] -> Image Source

A uniform cubic B-spline with the given control points.

bSpline' :: [Point] -> Image Source

A B-spline which starts in the first control point and ends in the last control point. This is achieved by adding two extra copies of the first and last points.

closedBSpline :: [Point] -> Image Source

A closed B-spline.

closedBSpline ps = bSpline (ps ++ take 3 ps)

bezier :: [Point] -> Image Source

A strip of cubic Bézier curves.

bezierSegment :: [Point] -> Image Source

A Bézier curve of degree n with the given control points [p0 .. pn].

Operating on curves

reverseImage :: Image -> Image Source

Reverse the direction of all curves in an image. Useful in conjunction with +++.

(+++) :: Image -> Image -> Image infixr 8 Source

Join the right-most curve of the first image to the left-most curve of the second image. The Style is inherited from the curve of the first image. If the end point of the first curve does not coincide with the starting point of the second curve a straight line is added to connect the two. This combinator is useful when using parameterized line styles (such as dashed).

(+.+) :: Image -> Image -> Image Source

Like +++ but doesn't join the end points of the curves.

(<++) :: Point -> Image -> Image infixr 8 Source

Prepend a point to the left-most curve of an image. p <++ i is equivalent to line p q +++ i if q is the starting point of the left-most curve of i.

(++>) :: Image -> Point -> Image infixl 9 Source

Append a point to the right-most curve of an image. i ++> p is equivalent to i +++ line q p if q is the end point of the right-most curve of i.

differentiate :: Image -> Image Source

Differentiating the curves of an image

mapImage :: (Scalar -> Point -> Point) -> Image -> Image Source

Apply a function to all points of an image. The function also gets the curve parameter (between 0 and 1) of the given point. This applies after all transformations so the points are measured in pixels, unless the image is later unfrozen with unfreezeImage.

zipImage :: (Scalar -> Point -> Point -> Point) -> Image -> Image -> Image Source

Zipping two images. Both images must have the same number of curves combined in the same order. As with mapImage the zipping takes place after all transformations.

transformImage :: (forall a. Transformable a => Scalar -> a -> a) -> Image -> Image Source

Apply a transformation to an image. Unlike mapImage the transformation is applied immediately.

curveLength :: Scalar -> Image -> Scalar Source

Compute the length of the curves of an image by approximating it by a series of straight-line segments, each no longer than specified by the first argument.

Advanced image manipulation

freezeImageSize :: Point -> Image -> Image Source

Freeze the size of an image around the given point. Scaling the image will only affect the position of the image, not the size. Translation and rotation affect the image normally.

scaleFrom p (diag k) (freezeImageSize p i) == freezeImageSize p i

Scaling with non-uniform scale factors will still distort the image, however.

freezeImageOrientation :: Point -> Image -> Image Source

Freeze image orientation. Rotations of the image will only affect the position of the image, not its orientation. Translation and scaling affect the image normally.

rotateAround p a (freezeImageOrientation p i) == freezeImageOrientation p i

freezeImage :: Point -> Image -> Image Source

Freeze both the size and the orientation of an image.

freezeImage p i == freezeImageSize p i (freezeImageOrientation p i)

freezeImageStyle :: Image -> Image Source

Freeze the line style of an image. This means that the pixel parameters (distance along the curve and pixel position) are given as they are at this moment, and won't be affected by later transformations.

unfreezeImage :: Image -> Image Source

Unfreeze an image. After unfreezing any frozen features will be affected by transformations again.

Combining images

type BlendFunc = Maybe Colour -> Maybe Colour -> Maybe Colour Source

A blend function is used to compute the resulting colour when combineing two images.

combine :: BlendFunc -> Image -> Image -> Image Source

Combine two images using the specified blend function.

mapColour :: (Colour -> Colour) -> Image -> Image Source

Map a function over the colours of an image.

unionBlend :: BlendFunc Source

Alpha blend the first colour on top of the second colour.

intersectBlend :: BlendFunc Source

The alpha value of the result is the product of the alpha values of the two inputs.

diffBlend :: BlendFunc Source

Multiplies the alpha value of the first colour by 1 - the alpha value of the second colour.

(<>) :: Monoid m => m -> m -> m infixr 6

An infix synonym for mappend.

Since: 4.5.0.0

(><) :: Image -> Image -> Image infixr 7 Source

The intersection of two images.

(><) = combine intersectBlend

(<->) :: Image -> Image -> Image infixl 8 Source

Subtract the second image from the first.

(<->) = combine diffBlend

Query functions

imageBounds :: Image -> Segment Source

Compute the bounds of an image, returning a line segment from the bottom left corner to the top right corner of the bounding box. This function ignores line widths. Note that using pixel based features (for instance, produced by freezeImageSize) means that the bounds may become invalid if the image is scaled.

Image attributes

Image attributes control things like the colour and width of curves.

Rendering

autoFit :: Point -> Point -> Image -> Image Source

Scale the an image to fit inside the the box given by the two points (bottom-left and top-right corners).

autoStretch :: Point -> Point -> Image -> Image Source

Scale the an image to fit inside the the box given by the two points (bottom-left and top-right corners). Does not preserve aspect ratio.

renderImage Source

Arguments

:: FilePath

File in which to store the image

-> Int

Image width

-> Int

Image height

-> Colour

Background colour

-> Image

Image to render

-> IO () 

Render an image as a PNG file with a 1-bit alpha channel. Semi-transparent pixels in the image are blended with the given background colour to produce opaque pixels.

Other