Copyright | (c) 2011 diagrams-lib team (see LICENSE) |
---|---|
License | BSD-style (see LICENSE) |
Maintainer | diagrams-discuss@googlegroups.com |
Safe Haskell | None |
Language | Haskell2010 |
Transformations specific to two dimensions, with a few generic transformations (uniform scaling, translation) also re-exported for convenience.
- rotation :: Angle -> T2
- rotate :: (Transformable t, V t ~ R2) => Angle -> t -> t
- rotateBy :: (Transformable t, V t ~ R2) => Double -> t -> t
- rotationAbout :: P2 -> Angle -> T2
- rotateAbout :: (Transformable t, V t ~ R2) => P2 -> Angle -> t -> t
- scalingX :: Double -> T2
- scaleX :: (Transformable t, V t ~ R2) => Double -> t -> t
- scalingY :: Double -> T2
- scaleY :: (Transformable t, V t ~ R2) => Double -> t -> t
- scaling :: (HasLinearMap v, Fractional (Scalar v)) => Scalar v -> Transformation v
- scale :: (Transformable t, Fractional (Scalar (V t)), Eq (Scalar (V t))) => Scalar (V t) -> t -> t
- scaleToX :: (Enveloped t, Transformable t, V t ~ R2) => Double -> t -> t
- scaleToY :: (Enveloped t, Transformable t, V t ~ R2) => Double -> t -> t
- scaleUToX :: (Enveloped t, Transformable t, V t ~ R2) => Double -> t -> t
- scaleUToY :: (Enveloped t, Transformable t, V t ~ R2) => Double -> t -> t
- translationX :: Double -> T2
- translateX :: (Transformable t, V t ~ R2) => Double -> t -> t
- translationY :: Double -> T2
- translateY :: (Transformable t, V t ~ R2) => Double -> t -> t
- translation :: HasLinearMap v => v -> Transformation v
- translate :: (Transformable t, HasLinearMap (V t)) => V t -> t -> t
- reflectionX :: T2
- reflectX :: (Transformable t, V t ~ R2) => t -> t
- reflectionY :: T2
- reflectY :: (Transformable t, V t ~ R2) => t -> t
- reflectionAbout :: P2 -> R2 -> T2
- reflectAbout :: (Transformable t, V t ~ R2) => P2 -> R2 -> t -> t
- shearingX :: Double -> T2
- shearX :: (Transformable t, V t ~ R2) => Double -> t -> t
- shearingY :: Double -> T2
- shearY :: (Transformable t, V t ~ R2) => Double -> t -> t
- onBasis :: Transformation R2 -> ((R2, R2), R2)
- avgScale :: T2 -> Double
Rotation
rotation :: Angle -> T2 Source
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 -> 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 Iso
s 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.
rotationAbout :: P2 -> Angle -> T2 Source
rotationAbout p
is a rotation about the point p
(instead of
around the local origin).
rotateAbout :: (Transformable t, V t ~ R2) => P2 -> Angle -> t -> t Source
rotateAbout p
is like rotate
, except it rotates around the
point p
instead of around the local origin.
Scaling
scalingX :: Double -> T2 Source
Construct a transformation which scales by the given factor in the x (horizontal) direction.
scaleX :: (Transformable t, V t ~ R2) => Double -> t -> t Source
Scale a diagram by the given factor in the x (horizontal)
direction. To scale uniformly, use scale
.
scalingY :: Double -> T2 Source
Construct a transformation which scales by the given factor in the y (vertical) direction.
scaleY :: (Transformable t, V t ~ R2) => Double -> t -> t Source
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 -> 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 :: (Enveloped t, Transformable t, V t ~ R2) => Double -> 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 :: (Enveloped t, Transformable t, V t ~ R2) => Double -> 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 :: (Enveloped t, Transformable t, V t ~ R2) => Double -> 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 :: Double -> T2 Source
Construct a transformation which translates by the given distance in the x (horizontal) direction.
translateX :: (Transformable t, V t ~ R2) => Double -> t -> t Source
Translate a diagram by the given distance in the x (horizontal) direction.
translationY :: Double -> T2 Source
Construct a transformation which translates by the given distance in the y (vertical) direction.
translateY :: (Transformable t, V t ~ R2) => Double -> t -> t Source
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 :: T2 Source
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 -> t Source
Flip a diagram from left to right, i.e. send the point (x,y) to (-x,y).
reflectionY :: T2 Source
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 -> t Source
Flip a diagram from top to bottom, i.e. send the point (x,y) to (x,-y).
reflectionAbout :: P2 -> R2 -> T2 Source
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 -> t Source
reflectAbout p v
reflects a diagram in the line determined by
the point p
and the vector v
.
Shears
shearingX :: Double -> T2 Source
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 -> t Source
shearX d
performs a shear in the x-direction which sends
(0,1)
to (d,1)
.
shearingY :: Double -> T2 Source
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 -> t Source
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 -> Double Source
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.