Copyright | (c) 2011 diagrams-core team (see LICENSE) |
---|---|
License | BSD-style (see LICENSE) |
Maintainer | diagrams-discuss@googlegroups.com |
Safe Haskell | None |
Language | Haskell2010 |
diagrams-core defines the core library of primitives forming the basis of an embedded domain-specific language for describing and rendering diagrams.
The Diagrams.Core.Envelope
module defines a data type and type class for
"envelopes", aka functional bounding regions.
- newtype Envelope v n = Envelope (Option (v n -> Max n))
- appEnvelope :: Envelope v n -> Maybe (v n -> n)
- onEnvelope :: ((v n -> n) -> v n -> n) -> Envelope v n -> Envelope v n
- mkEnvelope :: (v n -> n) -> Envelope v n
- pointEnvelope :: (Fractional n, Metric v) => Point v n -> Envelope v n
- class (Metric (V a), OrderedField (N a)) => Enveloped a where
- getEnvelope :: a -> Envelope (V a) (N a)
- diameter :: (V a ~ v, N a ~ n, Enveloped a) => v n -> a -> n
- radius :: (V a ~ v, N a ~ n, Enveloped a) => v n -> a -> n
- extent :: (V a ~ v, N a ~ n, Enveloped a) => v n -> a -> Maybe (n, n)
- size :: (V a ~ v, N a ~ n, Enveloped a, HasBasis v) => a -> v n
- envelopeVMay :: Enveloped a => Vn a -> a -> Maybe (Vn a)
- envelopeV :: Enveloped a => Vn a -> a -> Vn a
- envelopePMay :: (V a ~ v, N a ~ n, Enveloped a) => v n -> a -> Maybe (Point v n)
- envelopeP :: (V a ~ v, N a ~ n, Enveloped a) => v n -> a -> Point v n
- envelopeSMay :: (V a ~ v, N a ~ n, Enveloped a) => v n -> a -> Maybe n
- envelopeS :: (V a ~ v, N a ~ n, Enveloped a, Num n) => v n -> a -> n
- class (Floating s, Ord 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.
Show (Envelope v n) Source | |
Ord n => Monoid (Envelope v n) Source | |
Ord n => Semigroup (Envelope v n) Source | |
Wrapped (Envelope v n) Source | |
(Metric v, Fractional n) => HasOrigin (Envelope v n) Source | 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. |
(Metric v, Floating n) => Transformable (Envelope v n) Source | |
(Metric v, OrderedField n) => Enveloped (Envelope v n) Source | |
(Metric v, OrderedField n) => Juxtaposable (Envelope v n) Source | |
Rewrapped (Envelope v n) (Envelope v' n') Source | |
type Unwrapped (Envelope v n) = Option (v n -> Max n) Source | |
type N (Envelope v n) = n Source | |
type V (Envelope v n) = v Source |
appEnvelope :: Envelope v n -> Maybe (v n -> n) Source
onEnvelope :: ((v n -> n) -> v n -> n) -> Envelope v n -> Envelope v n Source
mkEnvelope :: (v n -> n) -> Envelope v n Source
pointEnvelope :: (Fractional n, Metric v) => Point v n -> Envelope v n Source
Create an envelope for the given point.
class (Metric (V a), OrderedField (N a)) => Enveloped a where Source
Enveloped
abstracts over things which have an envelope.
getEnvelope :: a -> Envelope (V a) (N 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] Source | |
Enveloped b => Enveloped (Set b) Source | |
Enveloped t => Enveloped (TransInv t) Source | |
(Enveloped a, Enveloped b, (~) (* -> *) (V a) (V b), (~) * (N a) (N b)) => Enveloped (a, b) Source | |
Enveloped b => Enveloped (Map k b) Source | |
(OrderedField n, Metric v) => Enveloped (Point v n) Source | |
(Metric v, OrderedField n) => Enveloped (Envelope v n) Source | |
(OrderedField n, Metric v, Monoid' m) => Enveloped (Subdiagram b v n m) Source | |
(Metric v, OrderedField n, Monoid' m) => Enveloped (QDiagram b v n m) Source |
Utility functions
diameter :: (V a ~ v, N a ~ n, Enveloped a) => v n -> a -> n Source
Compute the diameter of a enveloped object along a particular vector. Returns zero for the empty envelope.
radius :: (V a ~ v, N a ~ n, Enveloped a) => v n -> a -> n Source
Compute the "radius" (1/2 the diameter) of an enveloped object along a particular vector.
extent :: (V a ~ v, N a ~ n, Enveloped a) => v n -> a -> Maybe (n, n) 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.
size :: (V a ~ v, N a ~ n, Enveloped a, HasBasis v) => a -> v n Source
The smallest positive vector that bounds the envelope of an object.
envelopeVMay :: Enveloped a => Vn a -> a -> Maybe (Vn 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 => Vn a -> a -> Vn 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 :: (V a ~ v, N a ~ n, Enveloped a) => v n -> a -> Maybe (Point v n) Source
Compute the point on a separating hyperplane in the given
direction, or Nothing
for the empty envelope.
envelopeP :: (V a ~ v, N a ~ n, Enveloped a) => v n -> a -> Point v n Source
Compute the point on a separating hyperplane in the given direction. Returns the origin for the empty envelope.
envelopeSMay :: (V a ~ v, N a ~ n, Enveloped a) => v n -> a -> Maybe n Source
Equivalent to the norm of envelopeVMay
:
envelopeSMay v x == fmap norm (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 norm. However, it is more
efficient than calling norm on the results of those functions.
envelopeS :: (V a ~ v, N a ~ n, Enveloped a, Num n) => v n -> a -> n Source
Equivalent to the norm of envelopeV
:
envelopeS v x == norm (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 norm. However, it is more
efficient than calling norm on the results of those functions.
Miscellaneous
class (Floating s, Ord 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.
(Floating s, Ord s) => OrderedField s Source |