wumpus-drawing-0.9.0: High-level drawing objects built on Wumpus-Basic.

PortabilityGHC
Stabilityhighly unstable
MaintainerStephen Tetley <stephen.tetley@gmail.com>
Safe HaskellSafe-Infered

Wumpus.Drawing.Paths.Base

Contents

Description

Absolute path type - this should be more amenable for building complex drawings than the PrimPath type in Wumpus-Core.

Note - there is no concatenation (i.e. no Monoid instance), this is because concatenating ** absolute ** paths has no obvious interpretation - draw a join between the paths, move the second path to start where the first ends...

Use CatTrail from Wumpus-Basic if you need a relative-path like object that supports concatenation, then convert it in a final step to an AbsPath.

Synopsis

Absolute path type

data AbsPath u Source

Absolute path data type.

Instances

Functor AbsPath 
(Ord u, Tolerance u) => Eq (AbsPath u) 
Show u => Show (AbsPath u) 
(Real u, Floating u, Ord u, Tolerance u) => Rotate (AbsPath u)

This is expensive on paths - needs a traversal.

(Real u, Floating u, Ord u, Tolerance u) => RotateAbout (AbsPath u)

This is expensive on paths - needs a traversal.

(Floating u, Ord u, Tolerance u) => Scale (AbsPath u)

This is expensive on paths - needs a traversal.

Num u => Translate (AbsPath u)

Translate is cheap on AbsPath it just moves the start and end points. The path itself is otherwise built from vectors so it doesn't respond to translation (translate == id).

Construction

emptyPath :: Floating u => Point2 u -> AbsPath uSource

Create the empty path.

Note - an absolute path needs locating and cannot be built without a start point. Figuratively, the empty path is a path from the start point to the end point.

Thus AbsPath operates as a semigroup but not a monoid.

line1 :: Floating u => Point2 u -> Point2 u -> AbsPath uSource

Create an absolute path as a straight line between the supplied points.

curve1 :: (Floating u, Ord u, Tolerance u) => Point2 u -> Point2 u -> Point2 u -> Point2 u -> AbsPath uSource

Create an absolute path from a single cubic Bezier curve.

vertexPath :: (Floating u, Ord u, Tolerance u) => [Point2 u] -> AbsPath uSource

vertexPath throws a runtime error if the supplied list is empty.

curvePath :: (Floating u, Ord u, Tolerance u) => [Point2 u] -> AbsPath uSource

curvePath consumes 4 points from the list on the intial step (start, control1, control2, end) then steps through the list taking 3 points at a time thereafter (control1,control2, end). Leftover points are discarded.

curvePath throws a runtime error if the supplied list is has less than 4 elements (start, control1, control2, end).

controlCurve :: (Floating u, Ord u, Tolerance u) => Point2 u -> Radian -> Radian -> Point2 u -> AbsPath uSource

This is not an arc...

vectorPath :: (Floating u, Ord u, Tolerance u) => [Vec2 u] -> Point2 u -> AbsPath uSource

Queries

null :: AbsPath u -> BoolSource

Is the path empty?

length :: Num u => AbsPath u -> uSource

Length of the Path.

Length is the length of the path as it is drawn, it is not a count of the number or path segments.

Length is cached so this operation is cheap - though this puts a tax on the build operations.

Concat and extension

snocLine :: Floating u => AbsPath u -> Vec2 u -> AbsPath uSource

Extend the path with a straight line segment from the end-point defined by the supplied vector.

 infixl 5 `snocLine`

snocLineTo :: Floating u => AbsPath u -> Point2 u -> AbsPath uSource

Extend the path with a straight line segment from the end-point to the supplied point.

 infixl 5 `snocLineTo`

snocCurve :: (Floating u, Ord u, Tolerance u) => AbsPath u -> (Vec2 u, Vec2 u, Vec2 u) -> AbsPath uSource

Extend the path from the end-point with a Bezier curve segment formed by the supplied points.

 infixl 5 `snocCurve`

snocCurveTo :: (Floating u, Ord u, Tolerance u) => AbsPath u -> (Point2 u, Point2 u, Point2 u) -> AbsPath uSource

Extend the path from the end-point with a Bezier curve segment formed by the supplied points.

 infixl 5 `snocCurveTo`

Conversion

toPrimPath :: InterpretUnit u => AbsPath u -> Query u PrimPathSource

Turn a Path into an ordinary PrimPath.

Assumes path is properly formed - i.e. end point of one segment is the same point as the start point of the next segment.

Shortening

shortenPath :: (Real u, Floating u) => u -> u -> AbsPath u -> AbsPath uSource

sortenPath : left_dist * right_dist * path -> Path

shortenL :: (Real u, Floating u) => u -> AbsPath u -> AbsPath uSource

Note - shortening a line from the left by greater-than-or-equal its length is operationally equivalent to making a zero-length line at the end point.

shortenR :: (Real u, Floating u) => u -> AbsPath u -> AbsPath uSource

Note - shortening a line from the right by greater-than-or-equal its length is operationally equivalent to making a zero-length line at the start point.

Tips and inclination

inclinationL :: (Real u, Floating u) => AbsPath u -> RadianSource

Direction of empty path is considered to be 0.

inclinationR :: (Real u, Floating u) => AbsPath u -> RadianSource

Direction of empty path is considered to be 0.

isBezierL :: AbsPath u -> BoolSource

Is the left tip a Bezier curve?

isBezierR :: AbsPath u -> BoolSource

Is the right tip a Bezier curve?

Path anchors

atend :: (Real u, Floating u) => AbsPath u -> (Point2 u, Radian)Source

Views

data PathViewL u Source

Constructors

EmptyPathL 
(PathSegment u) :<< (AbsPath u) 

Instances

data PathViewR u Source

Constructors

EmptyPathR 
(AbsPath u) :>> (PathSegment u) 

Instances

data PathSegment u Source

PathSegments are annotated with length.

Constructors

LineSeg u (Point2 u) (Point2 u) 
CurveSeg u (Point2 u) (Point2 u) (Point2 u) (Point2 u) 

Instances

roundExterior :: (Real u, Floating u, Tolerance u) => u -> AbsPath u -> AbsPath uSource

Round a "closed" path.

Caution - all path sgements are expected to be longer than 2x the round corner length, though this is not checked..

roundInterior :: (Real u, Floating u, Tolerance u) => u -> AbsPath u -> AbsPath uSource

Round interior corners of a Path.

The path is treated as open - the start of the initial and end of the final segments are not rounded. Only straight line to straight line joins are rounded, joins to or from Bezier curves are not rounded.

Caution - all path segments are expected to be longer than 2x the round corner length, though this is not checked..

deBezier :: Floating u => AbsPath u -> AbsPath uSource

Redraw an AbsPath replacing the Bezier curves with three lines along the control vectors.

pathMajorPoints :: Num u => AbsPath u -> [Point2 u]Source

This does not extract the control points of Bezier curves.

pathAllPoints :: Num u => AbsPath u -> [Point2 u]Source

This extracts the control points of Bezier curves.

Path division

pathdiv :: (Real u, Floating u) => u -> u -> u -> AbsPath u -> [(Point2 u, Radian)]Source

Divide a path returning intermediate points and direction

Args are initial-prefix, division size, trailing size.

Generation is stopped if the remainder of the path is shorter than the trailing size.