Copyright | (c) 2011-2015 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.
- type T2 = Transformation V2
- rotation :: Floating n => Angle n -> Transformation V2 n
- rotate :: (InSpace V2 n t, Transformable t, Floating n) => Angle n -> t -> t
- rotateBy :: (InSpace V2 n t, Transformable t, Floating n) => n -> t -> t
- rotated :: (InSpace V2 n a, Floating n, SameSpace a b, Transformable a, Transformable b) => Angle n -> Iso a b a b
- rotationAround :: Floating n => P2 n -> Angle n -> T2 n
- rotateAround :: (InSpace V2 n t, Transformable t, Floating n) => P2 n -> Angle n -> t -> t
- rotationTo :: OrderedField n => Direction V2 n -> T2 n
- rotateTo :: (InSpace V2 n t, OrderedField n, Transformable t) => Direction V2 n -> t -> t
- scalingX :: (Additive v, R1 v, Fractional n) => n -> Transformation v n
- scaleX :: (InSpace v n t, R2 v, Fractional n, Transformable t) => n -> t -> t
- scalingY :: (Additive v, R2 v, Fractional n) => n -> Transformation v n
- scaleY :: (InSpace v n t, R2 v, Fractional n, Transformable t) => n -> t -> t
- scaling :: (Additive v, Fractional n) => n -> Transformation v n
- scale :: (InSpace v n a, Eq n, Fractional n, Transformable a) => n -> a -> a
- scaleToX :: (InSpace v n t, R2 v, Enveloped t, Transformable t) => n -> t -> t
- scaleToY :: (InSpace v n t, R2 v, Enveloped t, Transformable t) => n -> t -> t
- scaleUToX :: (InSpace v n t, R1 v, Enveloped t, Transformable t) => n -> t -> t
- scaleUToY :: (InSpace v n t, R2 v, Enveloped t, Transformable t) => n -> t -> t
- translationX :: (Additive v, R1 v, Num n) => n -> Transformation v n
- translateX :: (InSpace v n t, R1 v, Transformable t) => n -> t -> t
- translationY :: (Additive v, R2 v, Num n) => n -> Transformation v n
- translateY :: (InSpace v n t, R2 v, Transformable t) => n -> t -> t
- translation :: v n -> Transformation v n
- translate :: Transformable t => Vn t -> t -> t
- scalingRotationTo :: Floating n => V2 n -> T2 n
- scaleRotateTo :: (InSpace V2 n t, Transformable t, Floating n) => V2 n -> t -> t
- reflectionX :: (Additive v, R1 v, Num n) => Transformation v n
- reflectX :: (InSpace v n t, R1 v, Transformable t) => t -> t
- reflectionY :: (Additive v, R2 v, Num n) => Transformation v n
- reflectY :: (InSpace v n t, R2 v, Transformable t) => t -> t
- reflectionXY :: (Additive v, R2 v, Num n) => Transformation v n
- reflectXY :: (InSpace v n t, R2 v, Transformable t) => t -> t
- reflectionAbout :: OrderedField n => P2 n -> Direction V2 n -> T2 n
- reflectAbout :: (InSpace V2 n t, OrderedField n, Transformable t) => P2 n -> Direction V2 n -> t -> t
- shearingX :: Num n => n -> T2 n
- shearX :: (InSpace V2 n t, Transformable t) => n -> t -> t
- shearingY :: Num n => n -> T2 n
- shearY :: (InSpace V2 n t, Transformable t) => n -> t -> t
Documentation
type T2 = Transformation V2 Source #
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 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.
rotated :: (InSpace V2 n a, Floating n, SameSpace a b, Transformable a, Transformable b) => Angle n -> Iso a b a b Source #
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)
.