diagrams-lib-1.4.2.3: 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.TwoD.Curvature

Description

Compute curvature for segments in two dimensions.

Synopsis

Documentation

curvature #

Arguments

:: RealFloat n 
=> Segment Closed V2 n

Segment to measure on.

-> n

Parameter to measure at.

-> PosInf n

Result is a PosInf value where PosInfty represents infinite curvature or zero radius of curvature.

Curvature measures how curved the segment is at a point. One intuition for the concept is how much you would turn the wheel when driving a car along the curve. When the wheel is held straight there is zero curvature. When turning a corner to the left we will have positive curvature. When turning to the right we will have negative curvature.

Another way to measure this idea is to find the largest circle that we can push up against the curve and have it touch (locally) at exactly the point and not cross the curve. This is a tangent circle. The radius of that circle is the "Radius of Curvature" and it is the reciprocal of curvature. Note that if the circle is on the "left" of the curve, we have a positive radius, and if it is to the right we have a negative radius. Straight segments have an infinite radius which leads us to our representation. We result in a pair of numerator and denominator so we can include infinity and zero for both the radius and the curvature.

Lets consider the following curve:

The curve starts with positive curvature,

approaches zero curvature

then has negative curvature

{-# LANGUAGE GADTs #-}

import Diagrams.TwoD.Curvature
import Data.Monoid.Inf
import Diagrams.Coordinates

segmentA :: Segment Closed V2 Double
segmentA = Cubic (12 ^& 0) (8 ^& 10) (OffsetClosed (20 ^& 8))

curveA = lw thick . strokeP . fromSegments $ [segmentA]

diagramA = pad 1.1 . centerXY $ curveA

diagramPos = diagramWithRadius 0.2

diagramZero = diagramWithRadius 0.45

diagramNeg = diagramWithRadius 0.8

diagramWithRadius t = pad 1.1 . centerXY
         $ curveA
        <> showCurvature segmentA t
         # withEnvelope (curveA :: D V2 Double)
         # lc red

showCurvature :: Segment Closed V2 Double -> Double -> Diagram SVG
showCurvature bez@(Cubic b c (OffsetClosed d)) t
  | v == (0,0) = mempty
  | otherwise  = go (radiusOfCurvature bez t)
  where
    v@(x,y) = unr2 $ firstDerivative b c d t
    vp = (-y) ^& x

    firstDerivative b c d t = let tt = t*t in (3*(3*tt-4*t+1))*^b + (3*(2-3*t)*t)*^c + (3*tt)*^d

    go Infinity   = mempty
    go (Finite r) = (circle (abs r) # translate vpr
                 <> strokeP (origin ~~ (origin .+^ vpr)))
                  # moveTo (origin .+^ atParam bez t)
      where
        vpr = signorm vp ^* r

radiusOfCurvature #

Arguments

:: RealFloat n 
=> Segment Closed V2 n

Segment to measure on.

-> n

Parameter to measure at.

-> PosInf n

Result is a PosInf value where PosInfty represents infinite radius of curvature or zero curvature.

Reciprocal of curvature.

squaredCurvature :: RealFloat n => Segment Closed V2 n -> n -> PosInf n #

With squaredCurvature we can compute values in spaces that do not support sqrt and it is just as useful for relative ordering of curvatures or looking for zeros.

squaredRadiusOfCurvature :: RealFloat n => Segment Closed V2 n -> n -> PosInf n #

Reciprocal of squaredCurvature