Copyright | (c) 2011 diagrams-core team (see LICENSE) |
---|---|
License | BSD-style (see LICENSE) |
Maintainer | diagrams-discuss@googlegroups.com |
Safe Haskell | None |
Language | Haskell2010 |
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.
- newtype Envelope v = Envelope (Option (v -> Max (Scalar v)))
- appEnvelope :: Envelope v -> Maybe (v -> Scalar v)
- onEnvelope :: ((v -> Scalar v) -> v -> Scalar v) -> Envelope v -> Envelope v
- mkEnvelope :: (v -> Scalar v) -> Envelope v
- pointEnvelope :: (Fractional (Scalar v), InnerSpace v) => Point v -> Envelope v
- class (InnerSpace (V a), OrderedField (Scalar (V a))) => Enveloped a where
- getEnvelope :: a -> Envelope (V a)
- diameter :: Enveloped a => V a -> a -> Scalar (V a)
- radius :: Enveloped a => V a -> a -> Scalar (V a)
- extent :: Enveloped a => V a -> a -> Maybe (Scalar (V a), Scalar (V a))
- envelopeVMay :: Enveloped a => V a -> a -> Maybe (V a)
- envelopeV :: Enveloped a => V a -> a -> V a
- envelopePMay :: Enveloped a => V a -> a -> Maybe (Point (V a))
- envelopeP :: Enveloped a => V a -> a -> Point (V a)
- envelopeSMay :: Enveloped a => V a -> a -> Maybe (Scalar (V a))
- envelopeS :: (Enveloped a, Num (Scalar (V a))) => V a -> a -> Scalar (V a)
- class (Fractional s, Floating s, Ord s, AdditiveGroup s) => OrderedField s
Envelopes
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)
ontov
iss' *^ v
, thens' <= 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.
Action Name (Envelope v) | |
Show (Envelope v) | |
Ord (Scalar v) => Monoid (Envelope v) | |
Ord (Scalar v) => Semigroup (Envelope v) | |
Wrapped (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) | |
Rewrapped (Envelope v) (Envelope v') | |
type Unwrapped (Envelope v) = Option (v -> Max (Scalar v)) | |
type V (Envelope v) = v |
appEnvelope :: Envelope v -> Maybe (v -> Scalar v) Source
mkEnvelope :: (v -> Scalar v) -> Envelope v Source
pointEnvelope :: (Fractional (Scalar v), InnerSpace v) => Point v -> Envelope v Source
Create an envelope for the given point.
class (InnerSpace (V a), OrderedField (Scalar (V a))) => Enveloped a where Source
Enveloped
abstracts over things which have an envelope.
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.
Enveloped b => Enveloped [b] | |
Enveloped b => Enveloped (Set b) | |
(OrderedField (Scalar v), InnerSpace v) => Enveloped (Point v) | |
Enveloped t => Enveloped (TransInv t) | |
(InnerSpace v, OrderedField (Scalar v)) => Enveloped (Envelope v) | |
(Enveloped a, Enveloped b, (~) * (V a) (V b)) => Enveloped (a, b) | |
Enveloped b => Enveloped (Map k b) | |
(OrderedField (Scalar v), InnerSpace v, HasLinearMap v, Monoid' m) => Enveloped (Subdiagram b v m) | |
(HasLinearMap v, InnerSpace v, OrderedField (Scalar v), Monoid' m) => Enveloped (QDiagram b v m) |
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.
extent :: Enveloped a => V a -> a -> Maybe (Scalar (V a), Scalar (V a)) Source
Compute the range of an enveloped object along a certain
direction. Returns a pair of scalars (lo,hi)
such that the
object extends from (lo *^ v)
to (hi *^ v)
. Returns Nothing
for objects with an empty envelope.
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 a Source
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.
(Fractional s, Floating s, Ord s, AdditiveGroup s) => OrderedField s |