Portability | GHC |
---|---|
Stability | highly unstable |
Maintainer | Stephen Tetley <stephen.tetley@gmail.com> |
Safe Haskell | Safe-Infered |
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
.
- data AbsPath u
- type DAbsPath = AbsPath Double
- emptyPath :: Floating u => Point2 u -> AbsPath u
- line1 :: Floating u => Point2 u -> Point2 u -> AbsPath u
- curve1 :: (Floating u, Ord u, Tolerance u) => Point2 u -> Point2 u -> Point2 u -> Point2 u -> AbsPath u
- vertexPath :: (Floating u, Ord u, Tolerance u) => [Point2 u] -> AbsPath u
- curvePath :: (Floating u, Ord u, Tolerance u) => [Point2 u] -> AbsPath u
- controlCurve :: (Floating u, Ord u, Tolerance u) => Point2 u -> Radian -> Radian -> Point2 u -> AbsPath u
- vectorPath :: (Floating u, Ord u, Tolerance u) => [Vec2 u] -> Point2 u -> AbsPath u
- vectorPathTheta :: (Real u, Floating u, Tolerance u) => [Vec2 u] -> Radian -> Point2 u -> AbsPath u
- anaTrailPath :: (Floating u, Ord u, Tolerance u) => Point2 u -> AnaTrail u -> AbsPath u
- catTrailPath :: (Floating u, Ord u, Tolerance u) => Point2 u -> CatTrail u -> AbsPath u
- null :: AbsPath u -> Bool
- length :: Num u => AbsPath u -> u
- snocLine :: Floating u => AbsPath u -> Vec2 u -> AbsPath u
- snocLineTo :: Floating u => AbsPath u -> Point2 u -> AbsPath u
- snocCurve :: (Floating u, Ord u, Tolerance u) => AbsPath u -> (Vec2 u, Vec2 u, Vec2 u) -> AbsPath u
- snocCurveTo :: (Floating u, Ord u, Tolerance u) => AbsPath u -> (Point2 u, Point2 u, Point2 u) -> AbsPath u
- toPrimPath :: InterpretUnit u => AbsPath u -> Query u PrimPath
- renderPath :: InterpretUnit u => PathMode -> AbsPath u -> Image u (AbsPath u)
- renderPath_ :: InterpretUnit u => PathMode -> AbsPath u -> Graphic u
- shortenPath :: (Real u, Floating u) => u -> u -> AbsPath u -> AbsPath u
- shortenL :: (Real u, Floating u) => u -> AbsPath u -> AbsPath u
- shortenR :: (Real u, Floating u) => u -> AbsPath u -> AbsPath u
- tipL :: AbsPath u -> Point2 u
- tipR :: AbsPath u -> Point2 u
- inclinationL :: (Real u, Floating u) => AbsPath u -> Radian
- inclinationR :: (Real u, Floating u) => AbsPath u -> Radian
- isBezierL :: AbsPath u -> Bool
- isBezierR :: AbsPath u -> Bool
- midway :: (Real u, Floating u) => AbsPath u -> (Point2 u, Radian)
- midway_ :: (Real u, Floating u) => AbsPath u -> Point2 u
- atstart :: (Real u, Floating u) => AbsPath u -> (Point2 u, Radian)
- atstart_ :: AbsPath u -> Point2 u
- atend :: (Real u, Floating u) => AbsPath u -> (Point2 u, Radian)
- atend_ :: AbsPath u -> Point2 u
- data PathViewL u
- = EmptyPathL
- | (PathSegment u) :<< (AbsPath u)
- type DPathViewL = PathViewL Double
- data PathViewR u
- = EmptyPathR
- | (AbsPath u) :>> (PathSegment u)
- type DPathViewR = PathViewR Double
- data PathSegment u
- type DPathSegment = PathSegment Double
- pathViewL :: Num u => AbsPath u -> PathViewL u
- pathViewR :: Num u => AbsPath u -> PathViewR u
- optimizeLines :: (Real u, Floating u, Ord u, Tolerance u) => AbsPath u -> AbsPath u
- roundExterior :: (Real u, Floating u, Tolerance u) => u -> AbsPath u -> AbsPath u
- roundInterior :: (Real u, Floating u, Tolerance u) => u -> AbsPath u -> AbsPath u
- deBezier :: Floating u => AbsPath u -> AbsPath u
- pathMajorPoints :: Num u => AbsPath u -> [Point2 u]
- pathAllPoints :: Num u => AbsPath u -> [Point2 u]
- pathdiv :: (Real u, Floating u) => u -> u -> u -> AbsPath u -> [(Point2 u, Radian)]
Absolute path type
Absolute path data type.
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...
vectorPathTheta :: (Real u, Floating u, Tolerance u) => [Vec2 u] -> Radian -> Point2 u -> AbsPath uSource
Queries
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.
renderPath :: InterpretUnit u => PathMode -> AbsPath u -> Image u (AbsPath u)Source
renderPath_ :: InterpretUnit u => PathMode -> AbsPath u -> Graphic uSource
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.
Path anchors
Views
EmptyPathL | |
(PathSegment u) :<< (AbsPath u) |
type DPathViewL = PathViewL DoubleSource
EmptyPathR | |
(AbsPath u) :>> (PathSegment u) |
type DPathViewR = PathViewR DoubleSource
data PathSegment u Source
PathSegments are annotated with length.
Functor PathSegment | |
(Ord u, Tolerance u) => Eq (PathSegment u) | |
Show u => Show (PathSegment u) |
type DPathSegment = PathSegment DoubleSource
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.