diagrams-lib-1.4.2.1: Embedded domain-specific language for declarative graphics

Copyright(c) 2011-2015 diagrams-lib team (see LICENSE)
LicenseBSD-style (see LICENSE)
Maintainerdiagrams-discuss@googlegroups.com
Safe HaskellNone
LanguageHaskell2010

Diagrams.TwoD.Transform

Contents

Description

Transformations specific to two dimensions, with a few generic transformations (uniform scaling, translation) also re-exported for convenience.

Synopsis

Documentation

Rotation

rotation :: Floating n => Angle n -> Transformation V2 n Source #

Create a transformation which performs a rotation about the local origin by the given angle. See also rotate.

rotate :: (InSpace V2 n t, Transformable t, Floating n) => Angle n -> t -> t Source #

Rotate about the local origin by the given angle. Positive angles correspond to counterclockwise rotation, negative to clockwise. The angle can be expressed using any of the Isos on Angle. For example, rotate (1/4 @@ turn), rotate (tau/4 @@ rad), and rotate (90 @@ deg) all represent the same transformation, namely, a counterclockwise rotation by a right angle. To rotate about some point other than the local origin, see rotateAbout.

Note that writing rotate (1/4), with no Angle constructor, will yield an error since GHC cannot figure out which sort of angle you want to use. In this common situation you can use rotateBy, which interprets its argument as a number of turns.

rotateBy :: (InSpace V2 n t, Transformable t, Floating n) => n -> t -> t Source #

A synonym for rotate, interpreting its argument in units of turns; it can be more convenient to write rotateBy (1/4) than rotate (1/4 @@ turn).

rotated :: (InSpace V2 n a, Floating n, SameSpace a b, Transformable a, Transformable b) => Angle n -> Iso a b a b Source #

Use an Angle to make an Iso between an object rotated and unrotated. This us useful for performing actions under a rotation:

under (rotated t) f = rotate (negated t) . f . rotate t
rotated t ## a      = rotate t a
a ^. rotated t      = rotate (-t) a
over (rotated t) f  = rotate t . f . rotate (negated t)

rotationAround :: Floating n => P2 n -> Angle n -> T2 n Source #

rotationAbout p is a rotation about the point p (instead of around the local origin).

rotateAround :: (InSpace V2 n t, Transformable t, Floating n) => P2 n -> Angle n -> t -> t Source #

rotateAbout p is like rotate, except it rotates around the point p instead of around the local origin.

rotationTo :: OrderedField n => Direction V2 n -> T2 n Source #

The rotation that aligns the x-axis with the given direction.

rotateTo :: (InSpace V2 n t, OrderedField n, Transformable t) => Direction V2 n -> t -> t Source #

Rotate around the local origin such that the x axis aligns with the given direction.

Scaling

scalingX :: (Additive v, R1 v, Fractional n) => n -> Transformation v n Source #

Construct a transformation which scales by the given factor in the x (horizontal) direction.

scaleX :: (InSpace v n t, R2 v, Fractional n, Transformable t) => n -> t -> t Source #

Scale a diagram by the given factor in the x (horizontal) direction. To scale uniformly, use scale.

scalingY :: (Additive v, R2 v, Fractional n) => n -> Transformation v n Source #

Construct a transformation which scales by the given factor in the y (vertical) direction.

scaleY :: (InSpace v n t, R2 v, Fractional n, Transformable t) => n -> t -> t Source #

Scale a diagram by the given factor in the y (vertical) direction. To scale uniformly, use scale.

scaling :: (Additive v, Fractional n) => n -> Transformation v n #

Create a uniform scaling transformation.

scale :: (InSpace v n a, Eq n, Fractional n, Transformable a) => n -> a -> a #

Scale uniformly in every dimension by the given scalar.

scaleToX :: (InSpace v n t, R2 v, Enveloped t, Transformable t) => n -> t -> t Source #

scaleToX w scales a diagram in the x (horizontal) direction by whatever factor required to make its width w. scaleToX should not be applied to diagrams with a width of 0, such as vrule.

scaleToY :: (InSpace v n t, R2 v, Enveloped t, Transformable t) => n -> t -> t Source #

scaleToY h scales a diagram in the y (vertical) direction by whatever factor required to make its height h. scaleToY should not be applied to diagrams with a height of 0, such as hrule.

scaleUToX :: (InSpace v n t, R1 v, Enveloped t, Transformable t) => n -> t -> t Source #

scaleUToX w scales a diagram uniformly by whatever factor required to make its width w. scaleUToX should not be applied to diagrams with a width of 0, such as vrule.

scaleUToY :: (InSpace v n t, R2 v, Enveloped t, Transformable t) => n -> t -> t Source #

scaleUToY h scales a diagram uniformly by whatever factor required to make its height h. scaleUToY should not be applied to diagrams with a height of 0, such as hrule.

Translation

translationX :: (Additive v, R1 v, Num n) => n -> Transformation v n Source #

Construct a transformation which translates by the given distance in the x (horizontal) direction.

translateX :: (InSpace v n t, R1 v, Transformable t) => n -> t -> t Source #

Translate a diagram by the given distance in the x (horizontal) direction.

translationY :: (Additive v, R2 v, Num n) => n -> Transformation v n Source #

Construct a transformation which translates by the given distance in the y (vertical) direction.

translateY :: (InSpace v n t, R2 v, Transformable t) => n -> t -> t Source #

Translate a diagram by the given distance in the y (vertical) direction.

translation :: v n -> Transformation v n #

Create a translation.

translate :: Transformable t => Vn t -> t -> t #

Translate by a vector.

Conformal affine maps

scalingRotationTo :: Floating n => V2 n -> T2 n Source #

The angle-preserving linear map that aligns the x-axis unit vector with the given vector. See also scaleRotateTo.

scaleRotateTo :: (InSpace V2 n t, Transformable t, Floating n) => V2 n -> t -> t Source #

Rotate and uniformly scale around the local origin such that the x-axis aligns with the given vector. This satisfies the equation

scaleRotateTo v = rotateTo (dir v) . scale (norm v)

up to floating point rounding errors, but is more accurate and performant since it avoids cancellable uses of trigonometric functions.

Reflection

reflectionX :: (Additive v, R1 v, Num n) => Transformation v n Source #

Construct a transformation which flips a diagram from left to right, i.e. sends the point (x,y) to (-x,y).

reflectX :: (InSpace v n t, R1 v, Transformable t) => t -> t Source #

Flip a diagram from left to right, i.e. send the point (x,y) to (-x,y).

reflectionY :: (Additive v, R2 v, Num n) => Transformation v n Source #

Construct a transformation which flips a diagram from top to bottom, i.e. sends the point (x,y) to (x,-y).

reflectY :: (InSpace v n t, R2 v, Transformable t) => t -> t Source #

Flip a diagram from top to bottom, i.e. send the point (x,y) to (x,-y).

reflectionXY :: (Additive v, R2 v, Num n) => Transformation v n Source #

Construct a transformation which flips the diagram about x=y, i.e. sends the point (x,y) to (y,x).

reflectXY :: (InSpace v n t, R2 v, Transformable t) => t -> t Source #

Flips the diagram about x=y, i.e. send the point (x,y) to (y,x).

reflectionAbout :: OrderedField n => P2 n -> Direction V2 n -> T2 n Source #

reflectionAbout p d is a reflection in the line determined by the point p and direction d.

reflectAbout :: (InSpace V2 n t, OrderedField n, Transformable t) => P2 n -> Direction V2 n -> t -> t Source #

reflectAbout p d reflects a diagram in the line determined by the point p and direction d.

Shears

shearingX :: Num n => n -> T2 n Source #

shearingX d is the linear transformation which is the identity on y coordinates and sends (0,1) to (d,1).

shearX :: (InSpace V2 n t, Transformable t) => n -> t -> t Source #

shearX d performs a shear in the x-direction which sends (0,1) to (d,1).

shearingY :: Num n => n -> T2 n Source #

shearingY d is the linear transformation which is the identity on x coordinates and sends (1,0) to (1,d).

shearY :: (InSpace V2 n t, Transformable t) => n -> t -> t Source #

shearY d performs a shear in the y-direction which sends (1,0) to (1,d).