diagrams-core-0.5.0.1: Core libraries for diagrams EDSL

Maintainerdiagrams-discuss@googlegroups.com
Safe HaskellNone

Graphics.Rendering.Diagrams.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*. Intuitively, the envelope 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 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.

This could probably be expressed in terms of a Galois connection; this is left as an exercise for the reader.

There is also a special "empty envelope".

Essentially, envelopes 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.

Constructors

Envelope 

Fields

unEnvelope :: Option (v -> Max (Scalar v))
 

Instances

Show (Envelope v) 
Ord (Scalar v) => Monoid (Envelope v) 
Ord (Scalar v) => Semigroup (Envelope v) 
(InnerSpace v, AdditiveGroup (Scalar 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), AdditiveGroup (Scalar v)) => Transformable (Envelope v) 
(InnerSpace v, OrderedField (Scalar v)) => Enveloped (Envelope v) 
(InnerSpace v, OrderedField (Scalar v)) => Juxtaposable (Envelope v) 
Newtype (QDiagram b v m) (UDTree (UpAnnots v m) (DownAnnots v) (Prim b v)) 

inEnvelope :: (Option (v -> Max (Scalar v)) -> Option (v -> Max (Scalar v))) -> Envelope v -> Envelope vSource

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

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

Enveloped abstracts over things which have an envelope.

Methods

getEnvelope :: b -> Envelope (V b)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.

data LocatedEnvelope v Source

A LocatedEnvelope value represents an envelope with its base point at a particular location.

Constructors

LocatedEnvelope (Point v) (TransInv (Envelope v)) 

location :: LocatedEnvelope v -> Point vSource

Get the location of a located envelope.

locateEnvelope :: Point v -> Envelope v -> LocatedEnvelope vSource

Create a LocatedEnvelope value by specifying a location and an envelope.

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.

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.

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.

boundaryFrom :: (OrderedField (Scalar v), InnerSpace v) => LocatedEnvelope v -> v -> Point vSource

boundaryFrom v b computes the point on the boundary of the located envelope b in the direction of v from the bounding region's base point. This is most often used to compute a point on the boundary of a named subdiagram.

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