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

Copyright(c) 2013 diagrams-lib team (see LICENSE)
LicenseBSD-style (see LICENSE)
Maintainerdiagrams-discuss@googlegroups.com
Safe HaskellNone
LanguageHaskell2010

Diagrams.Tangent

Contents

Description

Computing tangent and normal vectors for segments and trails.

Synopsis

Tangents

tangentAtParam :: Parametric (Tangent t) => t -> N t -> Vn t Source #

Compute the tangent vector to a segment or trail at a particular parameter.

Examples of more specific types this function can have include

  • Segment Closed V2 -> Double -> V2 Double
  • Trail' Line V2 -> Double -> V2 Double
  • Located (Trail V2) -> Double -> V2 Double

See the instances listed for the Tangent newtype for more.

tangentAtStart :: EndValues (Tangent t) => t -> Vn t Source #

Compute the tangent vector at the start of a segment or trail.

tangentAtEnd :: EndValues (Tangent t) => t -> Vn t Source #

Compute the tangent vector at the end of a segment or trail.

Normals

normalAtParam :: (InSpace V2 n t, Parametric (Tangent t), Floating n) => t -> n -> V2 n Source #

Compute the (unit) normal vector to a segment or trail at a particular parameter.

Examples of more specific types this function can have include

  • Segment Closed V2 Double -> Double -> V2 Double
  • Trail' Line V2 Double -> Double -> V2 Double
  • Located (Trail V2 Double) -> Double -> V2 Double

See the instances listed for the Tangent newtype for more.

normalAtStart :: (InSpace V2 n t, EndValues (Tangent t), Floating n) => t -> V2 n Source #

Compute the normal vector at the start of a segment or trail.

normalAtEnd :: (InSpace V2 n t, EndValues (Tangent t), Floating n) => t -> V2 n Source #

Compute the normal vector at the end of a segment or trail.

Tangent newtype

newtype Tangent t Source #

A newtype wrapper used to give different instances of Parametric and EndValues that compute tangent vectors.

Constructors

Tangent t 

Instances

(DomainBounds t, EndValues (Tangent t)) => EndValues (Tangent (Located t)) Source # 
(Additive v, Num n) => EndValues (Tangent (FixedSegment v n)) Source # 
(Additive v, Num n) => EndValues (Tangent (Segment Closed v n)) Source # 
(Metric v, OrderedField n, Real n) => EndValues (Tangent (Trail v n)) Source # 

Methods

atStart :: Tangent (Trail v n) -> Codomain (Tangent (Trail v n)) (N (Tangent (Trail v n))) Source #

atEnd :: Tangent (Trail v n) -> Codomain (Tangent (Trail v n)) (N (Tangent (Trail v n))) Source #

(Parametric (GetSegment (Trail' c v n)), EndValues (GetSegment (Trail' c v n)), Additive v, Num n) => EndValues (Tangent (Trail' c v n)) Source # 

Methods

atStart :: Tangent (Trail' c v n) -> Codomain (Tangent (Trail' c v n)) (N (Tangent (Trail' c v n))) Source #

atEnd :: Tangent (Trail' c v n) -> Codomain (Tangent (Trail' c v n)) (N (Tangent (Trail' c v n))) Source #

DomainBounds t => DomainBounds (Tangent t) Source # 
Parametric (Tangent t) => Parametric (Tangent (Located t)) Source # 
(Additive v, Num n) => Parametric (Tangent (FixedSegment v n)) Source # 
(Additive v, Num n) => Parametric (Tangent (Segment Closed v n)) Source # 
(Metric v, OrderedField n, Real n) => Parametric (Tangent (Trail v n)) Source # 

Methods

atParam :: Tangent (Trail v n) -> N (Tangent (Trail v n)) -> Codomain (Tangent (Trail v n)) (N (Tangent (Trail v n))) Source #

(Parametric (GetSegment (Trail' c v n)), Additive v, Num n) => Parametric (Tangent (Trail' c v n)) Source # 

Methods

atParam :: Tangent (Trail' c v n) -> N (Tangent (Trail' c v n)) -> Codomain (Tangent (Trail' c v n)) (N (Tangent (Trail' c v n))) Source #

type V (Tangent t) Source # 
type V (Tangent t) = V t
type N (Tangent t) Source # 
type N (Tangent t) = N t
type Codomain (Tangent t) Source # 
type Codomain (Tangent t) = V t