diagrams-lib-0.7.1: 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 a => a -> 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 a) => a -> 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 type which is an instance of 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 type annotation, 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 is specialized to take a Turn argument.

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

A synonym for rotate, specialized to only work with Turn arguments; it can be more convenient to write rotateBy (1/4) than rotate (1/4 :: Turn).

rotationAbout :: Angle a => P2 -> a -> T2Source

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

rotateAbout :: (Transformable t, V t ~ R2, Angle a) => P2 -> a -> 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).

Scale invariance

data ScaleInv t Source

The ScaleInv wrapper creates two-dimensional scale-invariant objects. Intuitively, a scale-invariant object is affected by transformations like translations and rotations, but not by scales.

However, this is problematic when it comes to non-uniform scales (e.g. scaleX 2 . scaleY 3) since they can introduce a perceived rotational component. The prototypical example is an arrowhead on the end of a path, which should be scale-invariant. However, applying a non-uniform scale to the path but not the arrowhead would leave the arrowhead pointing in the wrong direction.

Moreover, for objects whose local origin is not at the local origin of the parent diagram, any scale can result in a translational component as well.

The solution is to also store a point (indicating the location, i.e. the local origin) and a unit vector (indicating the direction) along with a scale-invariant object. A transformation to be applied is decomposed into rotational and translational components as follows:

  • The transformation is applied to the direction vector, and the difference in angle between the original direction vector and its image under the transformation determines the rotational component. The rotation is applied with respect to the stored location, rather than the global origin.
  • The vector from the location to the image of the location under the transformation determines the translational component.

Constructors

ScaleInv 

Fields

unScaleInv :: t
 
scaleInvDir :: R2
 
scaleInvLoc :: P2
 

Instances

Show t => Show (ScaleInv t) 
(~ * (V t) R2, Transformable t) => IsPrim (ScaleInv t) 
(~ * (V t) R2, Transformable t) => Transformable (ScaleInv t) 
(~ * (V t) R2, HasOrigin t) => HasOrigin (ScaleInv t) 
(Renderable t b, ~ * (V t) R2) => Renderable (ScaleInv t) b 

scaleInv :: t -> R2 -> ScaleInv tSource

Create a scale-invariant object pointing in the given direction, located at the origin.

scaleInvPrim :: (Transformable t, Renderable t b, V t ~ R2, Monoid m) => t -> R2 -> QDiagram b R2 mSource

Create a diagram from a single scale-invariant primitive. The vector argument specifies the direction in which the primitive is "pointing" (for the purpose of keeping it rotated correctly under non-uniform scaling). The primitive is assumed to be "located" at the origin (for the purpose of translating it correctly under scaling).

Note that the resulting diagram will have an empty envelope, trace, and query. The reason is that the envelope, trace, and query cannot be cached---applying a transformation would cause the cached envelope, etc. to get "out of sync" with the scale-invariant object. The intention, at any rate, is that scale-invariant things will be used only as "decorations" (e.g. arrowheads) which should not affect the envelope, trace, and query.

component-wise

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.