diagrams-core-1.0: Core libraries for diagrams EDSL

Maintainerdiagrams-discuss@googlegroups.com
Safe HaskellNone

Diagrams.Core.Envelope

Contents

Description

Graphics.Rendering.Diagrams defines the core library of primitives forming the basis of an embedded domain-specific language for describing and rendering diagrams.

The Envelope module defines a data type and type class for "envelopes", aka functional bounding regions.

Synopsis

Envelopes

newtype Envelope v Source

Every diagram comes equipped with an envelope. What is an envelope?

Consider first the idea of a bounding box. A bounding box expresses the distance to a bounding plane in every direction parallel to an axis. That is, a bounding box can be thought of as the intersection of a collection of half-planes, two perpendicular to each axis.

More generally, the intersection of half-planes in every direction would give a tight "bounding region", or convex hull. However, representing such a thing intensionally would be impossible; hence bounding boxes are often used as an approximation.

An envelope is an extensional representation of such a "bounding region". Instead of storing some sort of direct representation, we store a function which takes a direction as input and gives a distance to a bounding half-plane as output. The important point is that envelopes can be composed, and transformed by any affine transformation.

Formally, given a vector v, the envelope computes a scalar s such that

  • for every point u inside the diagram, if the projection of (u - origin) onto v is s' *^ v, then s' <= s.
  • s is the smallest such scalar.

There is also a special "empty envelope".

The idea for envelopes came from Sebastian Setzer; see http://byorgey.wordpress.com/2009/10/28/collecting-attributes/#comment-2030. See also Brent Yorgey, Monoids: Theme and Variations, published in the 2012 Haskell Symposium: http://www.cis.upenn.edu/~byorgey/pub/monoid-pearl.pdf; video: http://www.youtube.com/watch?v=X-8NCkD2vOw.

Constructors

Envelope (Option (v -> Max (Scalar v))) 

Instances

Action Name (Envelope v) 
Show (Envelope v) 
Ord (Scalar v) => Monoid (Envelope v) 
Ord (Scalar v) => Semigroup (Envelope v) 
(InnerSpace v, Fractional (Scalar v)) => HasOrigin (Envelope v)

The local origin of an envelope is the point with respect to which bounding queries are made, i.e. the point from which the input vectors are taken to originate.

(HasLinearMap v, InnerSpace v, Floating (Scalar v)) => Transformable (Envelope v) 
(InnerSpace v, OrderedField (Scalar v)) => Enveloped (Envelope v) 
(InnerSpace v, OrderedField (Scalar v)) => Juxtaposable (Envelope v) 
(~ * (Scalar v) s, ~ * (Scalar v') s', ~ * s s') => Wrapped (Option (v -> Max s)) (Option (v' -> Max s')) (Envelope v) (Envelope v') 
Wrapped (DUALTree (DownAnnots v) (UpAnnots b v m) () (QDiaLeaf b v m)) (DUALTree (DownAnnots v') (UpAnnots b' v' m') () (QDiaLeaf b' v' m')) (QDiagram b v m) (QDiagram b' v' m') 

onEnvelope :: ((v -> Scalar v) -> v -> Scalar v) -> Envelope v -> Envelope vSource

pointEnvelope :: (Fractional (Scalar v), InnerSpace v) => Point v -> Envelope vSource

Create an envelope for the given point.

class (InnerSpace (V a), OrderedField (Scalar (V a))) => Enveloped a whereSource

Enveloped abstracts over things which have an envelope.

Methods

getEnvelope :: a -> Envelope (V a)Source

Compute the envelope of an object. For types with an intrinsic notion of "local origin", the envelope will be based there. Other types (e.g. Trail) may have some other default reference point at which the envelope will be based; their instances should document what it is.

Utility functions

diameter :: Enveloped a => V a -> a -> Scalar (V a)Source

Compute the diameter of a enveloped object along a particular vector. Returns zero for the empty envelope.

radius :: Enveloped a => V a -> a -> Scalar (V a)Source

Compute the "radius" (1/2 the diameter) of an enveloped object along a particular vector.

envelopeVMay :: Enveloped a => V a -> a -> Maybe (V a)Source

Compute the vector from the local origin to a separating hyperplane in the given direction, or Nothing for the empty envelope.

envelopeV :: Enveloped a => V a -> a -> V aSource

Compute the vector from the local origin to a separating hyperplane in the given direction. Returns the zero vector for the empty envelope.

envelopePMay :: Enveloped a => V a -> a -> Maybe (Point (V a))Source

Compute the point on a separating hyperplane in the given direction, or Nothing for the empty envelope.

envelopeP :: Enveloped a => V a -> a -> Point (V a)Source

Compute the point on a separating hyperplane in the given direction. Returns the origin for the empty envelope.

envelopeSMay :: Enveloped a => V a -> a -> Maybe (Scalar (V a))Source

Equivalent to the magnitude of envelopeVMay:

 envelopeSMay v x == fmap magnitude (envelopeVMay v x)

(other than differences in rounding error)

Note that the envelopeVMay / envelopePMay functions above should be preferred, as this requires a call to magnitude. However, it is more efficient than calling magnitude on the results of those functions.

envelopeS :: (Enveloped a, Num (Scalar (V a))) => V a -> a -> Scalar (V a)Source

Equivalent to the magnitude of envelopeV:

 envelopeS v x == magnitude (envelopeV v x)

(other than differences in rounding error)

Note that the envelopeV / envelopeP functions above should be preferred, as this requires a call to magnitude. However, it is more efficient than calling magnitude on the results of those functions.

Miscellaneous

class (Fractional s, Floating s, Ord s, AdditiveGroup s) => OrderedField s Source

When dealing with envelopes we often want scalars to be an ordered field (i.e. support all four arithmetic operations and be totally ordered) so we introduce this class as a convenient shorthand.

Instances