diagrams-lib-1.0: Embedded domain-specific language for declarative graphics

Maintainerdiagrams-discuss@googlegroups.com
Safe HaskellNone

Diagrams.Trace

Contents

Description

"Traces", aka embedded raytracers, for finding points on the edge of a diagram. See Diagrams.Core.Trace for internal implementation details.

Synopsis

Types

data Trace v

Every diagram comes equipped with a trace. Intuitively, the trace for a diagram is like a raytracer: given a line (represented as a base point and a direction), the trace computes the distance from the base point along the line to the first intersection with the diagram. The distance can be negative if the intersection is in the opposite direction from the base point, or infinite if the ray never intersects the diagram. Note: to obtain the distance to the furthest intersection instead of the closest, just negate the direction vector and then negate the result.

Note that the output should actually be interpreted not as an absolute distance, but as a multiplier relative to the input vector. That is, if the input vector is v and the returned scalar is s, the distance from the base point to the intersection is given by s * magnitude v.

Instances

Action Name (Trace v) 
Show (Trace v) 
Ord (Scalar v) => Semigroup (Trace v) 
Ord (Scalar v) => Monoid (Trace v) 
(Ord (Scalar v), VectorSpace v) => Traced (Trace v) 
HasLinearMap v => Transformable (Trace v) 
VectorSpace v => HasOrigin (Trace v) 
(InnerSpace v, OrderedField (Scalar v)) => Alignable (Trace v) 
(~ * (Scalar v) s, ~ * (Scalar v') s', ~ * s s') => Wrapped (Point v -> v -> PosInf s) (Point v' -> v' -> PosInf s') (Trace v) (Trace 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') 

class (Ord (Scalar (V a)), VectorSpace (V a)) => Traced a

Traced abstracts over things which have a trace.

Instances

Traced b => Traced [b] 
Traced b => Traced (Set b) 
(Ord (Scalar v), VectorSpace v) => Traced (Trace v) 
Traced t => Traced (TransInv t) 
(Ord (Scalar v), VectorSpace v) => Traced (Point v)

The trace of a single point is the empty trace, i.e. the one which returns positive infinity for every query. Arguably it should return a finite distance for vectors aimed directly at the given point and infinity for everything else, but due to floating-point inaccuracy this is problematic. Note that the envelope for a single point is not the empty envelope (see Diagrams.Core.Envelope).

Traced a => Traced (Located a)

The trace of a Located a is the trace of the a, translated to the location.

Traced (FixedSegment R2) 
Traced (Trail R2) 
Traced (Path R2) 
(Traced a, Traced b, ~ * (V a) (V b)) => Traced (a, b) 
Traced b => Traced (Map k b) 
Traced (Segment Closed R2) 
(HasLinearMap v, VectorSpace v, Ord (Scalar v), InnerSpace v, Semigroup m, Fractional (Scalar v), Floating (Scalar v)) => Traced (QDiagram b v m) 
(OrderedField (Scalar v), HasLinearMap v, InnerSpace v, Semigroup m) => Traced (Subdiagram b v m) 

Diagram traces

trace :: (InnerSpace v, HasLinearMap v, OrderedField (Scalar v), Semigroup m) => Lens' (QDiagram b v m) (Trace v)

Get the trace of a diagram.

setTrace :: (OrderedField (Scalar v), InnerSpace v, HasLinearMap v, Semigroup m) => Trace v -> QDiagram b v m -> QDiagram b v m

Replace the trace of a diagram.

withTrace :: (HasLinearMap (V a), Traced a, OrderedField (Scalar (V a)), InnerSpace (V a), Monoid' m) => a -> QDiagram b (V a) m -> QDiagram b (V a) mSource

Use the trace from some object as the trace for a diagram, in place of the diagram's default trace.

Querying traces

traceV :: Traced a => Point (V a) -> V a -> a -> Maybe (V a)

Compute the vector from the given point to the boundary of the given object in the given direction, or Nothing if there is no intersection.

traceP :: Traced a => Point (V a) -> V a -> a -> Maybe (Point (V a))

Given a base point and direction, compute the closest point on the boundary of the given object, or Nothing if there is no intersection in the given direction.

maxTraceV :: Traced a => Point (V a) -> V a -> a -> Maybe (V a)

Like traceV, but computes a vector to the *furthest* point on the boundary instead of the closest.

maxTraceP :: Traced a => Point (V a) -> V a -> a -> Maybe (Point (V a))

Like traceP, but computes the *furthest* point on the boundary instead of the closest.

Subdiagram traces

boundaryFrom :: (HasLinearMap v, OrderedField (Scalar v), InnerSpace v, Semigroup m) => Subdiagram b v m -> v -> Point vSource

Compute the furthest point on the boundary of a subdiagram, beginning from the location (local origin) of the subdiagram and moving in the direction of the given vector. If there is no such point, the origin is returned; see also boundaryFromMay.

boundaryFromMay :: (HasLinearMap v, OrderedField (Scalar v), Semigroup m, InnerSpace v) => Subdiagram b v m -> v -> Maybe (Point v)Source

Compute the furthest point on the boundary of a subdiagram, beginning from the location (local origin) of the subdiagram and moving in the direction of the given vector, or Nothing if there is no such point.