diagrams-contrib-1.4: Collection of user contributions to diagrams EDSL

Copyright(c) 2016 Brent Yorgey
LicenseBSD-style (see LICENSE)
Maintainerbyorgey@gmail.com
Safe HaskellNone
LanguageHaskell2010

Diagrams.TwoD.Path.Follow

Description

An alternative monoid for trails which rotates trails so their starting and ending tangents match at join points.

Synopsis

Documentation

data Following n Source #

Following is just like Trail' Line V2, except that it has a different Monoid instance. Following values are concatenated, just like regular lines, except that they are also rotated so the tangents match at the join point. In addition, they are normalized so the tangent at the start point is in the direction of the positive x axis (essentially we are considering trails equivalent up to rotation).

Pro tip: you can concatenate a list of trails so their tangents match using ala from Control.Lens, like so:

ala follow foldMap :: [Trail' Line V2 n] -> Trail' Line V2 n

This is illustrated in the example below.

import Control.Lens (ala)
import Diagrams.TwoD.Path.Follow

wibble :: Trail' Line V2 Double
wibble = hrule 1 <> hrule 0.5 # rotateBy (1/6) <> hrule 0.5 # rotateBy (-1/6) <> a
  where a = arc (xDir # rotateBy (-1/4)) (1/5 @@ turn)
          # scale 0.7

followExample =
  [ wibble
  , wibble
    # replicate 5
    # ala follow foldMap
  ]
  # map stroke
  # map centerXY
  # vsep 1
  # frame 0.5

Instances

(Ord n, Floating n) => Monoid (Following n) Source # 
RealFloat n => Wrapped (Following n) Source #

Note this is only an iso when considering trails equivalent up to rotation.

Associated Types

type Unwrapped (Following n) :: * #

RealFloat n => Rewrapped (Following n) (Following n') Source # 
type Unwrapped (Following n) Source # 

follow :: RealFloat n => Trail' Line V2 n -> Following n Source #

Create a Following from a line, normalizing it (by rotation) so that it starts in the positive x direction.

unfollow :: Following n -> Trail' Line V2 n Source #

Project out the line from a Following.

If trails are considered equivalent up to rotation, then unfollow and follow are inverse.