Copyright | (c) 2011 diagrams-lib team (see LICENSE) |
---|---|
License | BSD-style (see LICENSE) |
Maintainer | diagrams-discuss@googlegroups.com |
Safe Haskell | None |
Language | Haskell2010 |
Two-dimensional arcs, approximated by cubic bezier curves.
- arc :: (InSpace V2 n t, OrderedField n, TrailLike t) => Direction V2 n -> Angle n -> t
- arc' :: (InSpace V2 n t, OrderedField n, TrailLike t) => n -> Direction V2 n -> Angle n -> t
- arcT :: OrderedField n => Direction V2 n -> Angle n -> Trail V2 n
- arcCCW :: (InSpace V2 n t, RealFloat n, TrailLike t) => Direction V2 n -> Direction V2 n -> t
- arcCW :: (InSpace V2 n t, RealFloat n, TrailLike t) => Direction V2 n -> Direction V2 n -> t
- bezierFromSweep :: OrderedField n => Angle n -> [Segment Closed V2 n]
- wedge :: (InSpace V2 n t, OrderedField n, TrailLike t) => n -> Direction V2 n -> Angle n -> t
- arcBetween :: (TrailLike t, V t ~ V2, N t ~ n, RealFloat n) => Point V2 n -> Point V2 n -> n -> t
- annularWedge :: (TrailLike t, V t ~ V2, N t ~ n, RealFloat n) => n -> n -> Direction V2 n -> Angle n -> t
Documentation
arc :: (InSpace V2 n t, OrderedField n, TrailLike t) => Direction V2 n -> Angle n -> t Source
Given a start direction d
and a sweep angle s
,
is the
path of a radius one arc starting at arc
d sd
and sweeping out the angle
s
counterclockwise (for positive s). The resulting
Trail
is allowed to wrap around and overlap itself.
arc' :: (InSpace V2 n t, OrderedField n, TrailLike t) => n -> Direction V2 n -> Angle n -> t Source
Given a radus r
, a start direction d
and an angle s
,
is the path of a radius arc'
r d s(abs r)
arc starting at
d
and sweeping out the angle s
counterclockwise (for positive
s). The origin of the arc is its center.
arc'Ex = mconcat [ arc' r xDir (1/4 @@ turn) | r <- [0.5,-1,1.5] ] # centerXY # pad 1.1
arcCCW :: (InSpace V2 n t, RealFloat n, TrailLike t) => Direction V2 n -> Direction V2 n -> t Source
Given a start direction s
and end direction e
, arcCCW s e
is the
path of a radius one arc counterclockwise between the two directions.
The origin of the arc is its center.
arcCW :: (InSpace V2 n t, RealFloat n, TrailLike t) => Direction V2 n -> Direction V2 n -> t Source
Like arcAngleCCW
but clockwise.
bezierFromSweep :: OrderedField n => Angle n -> [Segment Closed V2 n] Source
bezierFromSweep s
constructs a series of Cubic
segments that
start in the positive y direction and sweep counter clockwise
through the angle s
. If s
is negative, it will start in the
negative y direction and sweep clockwise. When s
is less than
0.0001 the empty list results. If the sweep is greater than fullTurn
later segments will overlap earlier segments.
wedge :: (InSpace V2 n t, OrderedField n, TrailLike t) => n -> Direction V2 n -> Angle n -> t Source
Create a circular wedge of the given radius, beginning at the given direction and extending through the given angle.
wedgeEx = hcat' (with & sep .~ 0.5) [ wedge 1 xDir (1/4 @@ turn) , wedge 1 (rotate (7/30 @@ turn) xDir) (4/30 @@ turn) , wedge 1 (rotate (1/8 @@ turn) xDir) (3/4 @@ turn) ] # fc blue # centerXY # pad 1.1
arcBetween :: (TrailLike t, V t ~ V2, N t ~ n, RealFloat n) => Point V2 n -> Point V2 n -> n -> t Source
arcBetween p q height
creates an arc beginning at p
and
ending at q
, with its midpoint at a distance of abs height
away from the straight line from p
to q
. A positive value of
height
results in an arc to the left of the line from p
to
q
; a negative value yields one to the right.
arcBetweenEx = mconcat [ arcBetween origin (p2 (2,1)) ht | ht <- [-0.2, -0.1 .. 0.2] ] # centerXY # pad 1.1
annularWedge :: (TrailLike t, V t ~ V2, N t ~ n, RealFloat n) => n -> n -> Direction V2 n -> Angle n -> t Source
Create an annular wedge of the given radii, beginning at the first direction and extending through the given sweep angle. The radius of the outer circle is given first.
annularWedgeEx = hsep 0.50 [ annularWedge 1 0.5 xDir (1/4 @@ turn) , annularWedge 1 0.3 (rotate (7/30 @@ turn) xDir) (4/30 @@ turn) , annularWedge 1 0.7 (rotate (1/8 @@ turn) xDir) (3/4 @@ turn) ] # fc blue # centerXY # pad 1.1