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

Maintainerdiagrams-discuss@googlegroups.com
Safe HaskellNone

Diagrams.ThreeD.Transform

Contents

Description

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

Synopsis

Rotation

aboutX :: Angle -> T3Source

Like aboutZ, but rotates about the X axis, bringing positive y-values towards the positive z-axis.

aboutY :: Angle -> T3Source

Like aboutZ, but rotates about the Y axis, bringing postive x-values towards the negative z-axis.

aboutZ :: Angle -> T3Source

Create a transformation which rotates by the given angle about a line parallel the Z axis passing through the local origin. A positive angle brings positive x-values towards the positive-y axis.

The angle can be expressed using any type which is an instance of Angle. For example, aboutZ (1/4 @@ turn), aboutZ (tau/4 @@ rad), and aboutZ (90 @@ deg) all represent the same transformation, namely, a counterclockwise rotation by a right angle. For more general rotations, see rotationAbout.

Note that writing aboutZ (1/4), with no type annotation, will yield an error since GHC cannot figure out which sort of angle you want to use.

rotationAboutSource

Arguments

:: Direction d 
=> P3

origin of rotation

-> d

direction of rotation axis

-> Angle

angle of rotation

-> T3 

rotationAbout p d a is a rotation about a line parallel to d passing through p.

pointAt :: Direction d => d -> d -> d -> T3Source

pointAt about initial final produces a rotation which brings the direction initial to point in the direction final by first panning around about, then tilting about the axis perpendicular to initial and final. In particular, if this can be accomplished without tilting, it will be, otherwise if only tilting is necessary, no panning will occur. The tilt will always be between ± /4 turn.

pointAt' :: R3 -> R3 -> R3 -> T3Source

pointAt' has the same behavior as pointAt, but takes vectors instead of directions.

Scaling

scalingX :: Double -> T3Source

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

scalingY :: Double -> T3Source

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

scalingZ :: Double -> T3Source

Construct a transformation which scales by the given factor in the z direction.

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

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

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

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

scaleZ :: (Transformable t, V t ~ R3) => Double -> t -> tSource

Scale a diagram by the given factor in the z 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.

Translation

translationX :: Double -> T3Source

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

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

Translate a diagram by the given distance in the x direction.

translationY :: Double -> T3Source

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

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

Translate a diagram by the given distance in the y direction.

translationZ :: Double -> T3Source

Construct a transformation which translates by the given distance in the z direction.

translateZ :: (Transformable t, V t ~ R3) => Double -> t -> tSource

Translate a diagram by the given distance in the y 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 :: T3Source

Construct a transformation which flips a diagram across x=0, i.e. sends the point (x,y,z) to (-x,y,z).

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

Flip a diagram across x=0, i.e. send the point (x,y,z) to (-x,y,z).

reflectionY :: T3Source

Construct a transformation which flips a diagram across y=0, i.e. sends the point (x,y,z) to (x,-y,z).

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

Flip a diagram across y=0, i.e. send the point (x,y,z) to (x,-y,z).

reflectionZ :: T3Source

Construct a transformation which flips a diagram across z=0, i.e. sends the point (x,y,z) to (x,y,-z).

reflectZ :: (Transformable t, V t ~ R3) => t -> tSource

Flip a diagram across z=0, i.e. send the point (x,y,z) to (x,y,-z).

reflectionAbout :: P3 -> R3 -> T3Source

reflectionAbout p v is a reflection across the plane through the point p and normal to vector v.

reflectAbout :: (Transformable t, V t ~ R3) => P3 -> R3 -> t -> tSource

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

Utilities for Backends

onBasis :: T3 -> ((R3, R3, R3), R3)Source

Get the matrix equivalent of an affine transform, as a triple of columns paired with the translation vector. This is mostly useful for implementing backends.