diagrams-core-1.0.0.1: Core libraries for diagrams EDSL

Maintainerdiagrams-discuss@googlegroups.com
Safe HaskellNone

Diagrams.Core.Trace

Contents

Description

diagrams-core defines the core library of primitives forming the basis of an embedded domain-specific language for describing and rendering diagrams.

The Trace module defines a data type and type class for "traces", aka functional boundaries, essentially corresponding to embedding a raytracer with each diagram.

Synopsis

Traces

newtype Trace v Source

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.

Constructors

Trace 

Fields

appTrace :: Point v -> v -> PosInf (Scalar v)
 

Instances

Action Name (Trace v) 
Show (Trace v) 
Ord (Scalar v) => Monoid (Trace v) 
Ord (Scalar v) => Semigroup (Trace v) 
VectorSpace v => HasOrigin (Trace v) 
HasLinearMap v => Transformable (Trace v) 
(Ord (Scalar v), VectorSpace v) => Traced (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') 

mkTrace :: (Point v -> v -> PosInf (Scalar v)) -> Trace vSource

Traced class

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

Traced abstracts over things which have a trace.

Methods

getTrace :: a -> Trace (V a)Source

Compute the trace of an object.

Instances

Traced b => Traced [b] 
Traced b => Traced (Set b) 
(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 t => Traced (TransInv t) 
(Ord (Scalar v), VectorSpace v) => Traced (Trace v) 
(Traced a, Traced b, ~ * (V a) (V b)) => Traced (a, b) 
Traced b => Traced (Map k b) 
(OrderedField (Scalar v), HasLinearMap v, InnerSpace v, Semigroup m) => Traced (Subdiagram b v m) 
(HasLinearMap v, VectorSpace v, Ord (Scalar v), InnerSpace v, Semigroup m, Fractional (Scalar v), Floating (Scalar v)) => Traced (QDiagram b v m) 

Computing with traces

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

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))Source

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)Source

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))Source

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