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

Maintainerdiagrams-discuss@googlegroups.com
Safe HaskellNone

Diagrams.TwoD.Transform

Contents

Description

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

Synopsis

Rotation

rotation :: Angle -> T2Source

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

rotate :: (Transformable t, V t ~ R2) => Angle -> t -> tSource

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 :: (Transformable t, V t ~ R2) => Double -> t -> tSource

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).

rotationAbout :: P2 -> Angle -> T2Source

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

rotateAbout :: (Transformable t, V t ~ R2) => P2 -> Angle -> t -> tSource

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

Scaling

scalingX :: Double -> T2Source

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

scaleX :: (Transformable t, V t ~ R2) => Double -> t -> tSource

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

scalingY :: Double -> T2Source

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

scaleY :: (Transformable t, V t ~ R2) => Double -> t -> tSource

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

scaling :: (HasLinearMap v, Fractional (Scalar v)) => Scalar v -> Transformation v

Create a uniform scaling transformation.

scale :: (Transformable t, Fractional (Scalar (V t)), Eq (Scalar (V t))) => Scalar (V t) -> t -> t

Scale uniformly in every dimension by the given scalar.

scaleToX :: (Enveloped t, Transformable t, V t ~ R2) => Double -> t -> tSource

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 :: (Enveloped t, Transformable t, V t ~ R2) => Double -> t -> tSource

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 :: (Enveloped t, Transformable t, V t ~ R2) => Double -> t -> tSource

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 :: (Enveloped t, Transformable t, V t ~ R2) => Double -> t -> tSource

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 :: Double -> T2Source

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

translateX :: (Transformable t, V t ~ R2) => Double -> t -> tSource

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

translationY :: Double -> T2Source

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

translateY :: (Transformable t, V t ~ R2) => Double -> t -> tSource

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

translation :: HasLinearMap v => v -> Transformation v

Create a translation.

translate :: (Transformable t, HasLinearMap (V t)) => V t -> t -> t

Translate by a vector.

Reflection

reflectionX :: T2Source

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

reflectX :: (Transformable t, V t ~ R2) => t -> tSource

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

reflectionY :: T2Source

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

reflectY :: (Transformable t, V t ~ R2) => t -> tSource

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

reflectionAbout :: P2 -> R2 -> T2Source

reflectionAbout p v is a reflection in the line determined by the point p and vector v.

reflectAbout :: (Transformable t, V t ~ R2) => P2 -> R2 -> t -> tSource

reflectAbout p v reflects a diagram in the line determined by the point p and the vector v.

Shears

shearingX :: Double -> T2Source

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

shearX :: (Transformable t, V t ~ R2) => Double -> t -> tSource

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

shearingY :: Double -> T2Source

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

shearY :: (Transformable t, V t ~ R2) => Double -> t -> tSource

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

Utilities

onBasis :: Transformation R2 -> ((R2, R2), R2)Source

Get the matrix equivalent of the linear transform, (as a pair of columns) and the translation vector. This is mostly useful for implementing backends.

avgScale :: T2 -> DoubleSource

Compute the "average" amount of scaling performed by a transformation. Satisfies the properties

   avgScale (scaling k) == k
   avgScale (t1  t2)  == avgScale t1 * avgScale t2

Backends which do not support stroking in the context of an arbitrary transformation may instead call avgScale on "frozen" transformations and multiply the line width by the resulting value.