Maintainer | diagrams-discuss@googlegroups.com |
---|
Graphics.Rendering.Diagrams defines the core library of primitives forming the basis of an embedded domain-specific language for describing and rendering diagrams.
The Bounds
module defines a data type and type class for functional
bounding regions.
- newtype Bounds v = Bounds {}
- class (InnerSpace (V b), OrderedField (Scalar (V b))) => Boundable b where
- diameter :: Boundable a => V a -> a -> Scalar (V a)
- radius :: Boundable a => V a -> a -> Scalar (V a)
- boundary :: Boundable a => V a -> a -> Point (V a)
- class (Fractional s, Floating s, Ord s, AdditiveGroup s) => OrderedField s
Bounding regions
Every diagram comes equipped with a bounding function.
Intuitively, the bounding function for a diagram tells us the
minimum distance we have to go in a given direction to get to a
(hyper)plane entirely containing the diagram on one side of
it. Formally, given a vector v
, it returns a scalar s
such
that
- for every vector
u
with its endpoint inside the diagram, if the projection ofu
ontov
iss' *^ v
, thens' <= s
. -
s
is the smallest such scalar.
This could probably be expressed in terms of a Galois connection; this is left as an exercise for the reader.
Essentially, bounding functions are a functional representation of (a conservative approximation to) convex bounding regions. The idea for this representation came from Sebastian Setzer; see http://byorgey.wordpress.com/2009/10/28/collecting-attributes/#comment-2030.
(Ord (Scalar v), AdditiveGroup (Scalar v)) => Monoid (Bounds v) | Bounding functions form a monoid, with the constantly zero
function (i.e. the empty region) as the identity, and pointwise
maximum as composition. Hence, if |
(InnerSpace v, AdditiveGroup (Scalar v), Fractional (Scalar v)) => HasOrigin (Bounds v) | The local origin of a bounding function 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), AdditiveGroup (Scalar v)) => Transformable (Bounds v) | |
(InnerSpace v, OrderedField (Scalar v)) => Boundable (Bounds v) |
class (InnerSpace (V b), OrderedField (Scalar (V b))) => Boundable b whereSource
Boundable
abstracts over things which can be bounded.
getBounds :: b -> Bounds (V b)Source
Given a boundable object, compute a functional bounding region
for it. For types with an intrinsic notion of "local
origin", the bounding function will be based there. Other
types (e.g. Trail
) may have some other default reference
point at which the bounding function will be based; their
instances should document what it is.
Boundable b => Boundable [b] | |
(InnerSpace v, OrderedField (Scalar v)) => Boundable (Bounds v) | |
(HasLinearMap v, InnerSpace v, OrderedField (Scalar v)) => Boundable (AnnDiagram b v m) |
Utility functions
diameter :: Boundable a => V a -> a -> Scalar (V a)Source
Compute the diameter of a boundable object along a particular vector.
radius :: Boundable a => V a -> a -> Scalar (V a)Source
Compute the radius (1/2 the diameter) of a boundable object along a particular vector.
boundary :: Boundable a => V a -> a -> Point (V a)Source
Compute the point along the boundary in the given direction.
Miscellaneous
class (Fractional s, Floating s, Ord s, AdditiveGroup s) => OrderedField s Source
When dealing with bounding regions 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 |