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

Copyright(c) 2012-2013 diagrams-lib team (see LICENSE)
LicenseBSD-style (see LICENSE)
Maintainerdiagrams-discuss@googlegroups.com
Safe HaskellNone
LanguageHaskell2010

Diagrams.Transform.ScaleInv

Description

Wrapper for creating scale-invariant objects in two dimensions.

Synopsis

Documentation

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

Instances

(Show t, Show (Vn t)) => Show (ScaleInv t) Source # 

Methods

showsPrec :: Int -> ScaleInv t -> ShowS #

show :: ScaleInv t -> String #

showList :: [ScaleInv t] -> ShowS #

((~) (* -> *) (V t) V2, (~) * (N t) n, RealFloat n, Transformable t) => Transformable (ScaleInv t) Source # 

Methods

transform :: Transformation (V (ScaleInv t)) (N (ScaleInv t)) -> ScaleInv t -> ScaleInv t #

((~) (* -> *) (V t) v, (~) * (N t) n, Additive v, Num n, HasOrigin t) => HasOrigin (ScaleInv t) Source # 

Methods

moveOriginTo :: Point (V (ScaleInv t)) (N (ScaleInv t)) -> ScaleInv t -> ScaleInv t #

((~) (* -> *) (V t) V2, (~) * (N t) n, RealFloat n, Renderable t b) => Renderable (ScaleInv t) b Source # 

Methods

render :: b -> ScaleInv t -> Render b (V (ScaleInv t)) (N (ScaleInv t)) #

type V (ScaleInv t) Source # 
type V (ScaleInv t) = V t
type N (ScaleInv t) Source # 
type N (ScaleInv t) = N t

scaleInvObj :: forall t. Lens' (ScaleInv t) t Source #

scaleInvDir :: forall t. Lens' (ScaleInv t) (Vn t) Source #

scaleInvLoc :: forall t. Lens' (ScaleInv t) (Point (V t) (N t)) Source #

scaleInv :: (V t ~ v, N t ~ n, Additive v, Num n) => t -> v n -> ScaleInv t Source #

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

scaleInvPrim :: (V t ~ V2, N t ~ n, RealFloat n, Typeable t, Renderable t b, Monoid m) => t -> V2 n -> QDiagram b (V t) (N t) m Source #

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.