| Copyright | (c) 2018 Mike Zuser |
|---|---|
| License | BSD-style (see LICENSE) |
| Maintainer | Mike Zuser <mikezuser@gmail.com> |
| Safe Haskell | Safe-Inferred |
| Language | Haskell2010 |
Diagrams.TwoD.Path.IntersectionExtras
Description
Extra functions for working with the intersections of Paths. This
module was motivated by explodeIntersections. The rest of the module is
either functions that where needed to build it or functions to help
consume it.
Synopsis
- intersectParams :: (InSpace V2 n t, SameSpace t s, ToPath t, ToPath s, OrderedField n) => t -> s -> ([[n]], [[n]])
- intersectParams' :: (InSpace V2 n t, SameSpace t s, ToPath t, ToPath s, OrderedField n) => n -> t -> s -> ([[n]], [[n]])
- intersectParamsP :: OrderedField n => Path V2 n -> Path V2 n -> ([[n]], [[n]])
- intersectParamsP' :: OrderedField n => n -> Path V2 n -> Path V2 n -> ([[n]], [[n]])
- intersectParamsT :: OrderedField n => Located (Trail V2 n) -> Located (Trail V2 n) -> ([n], [n])
- intersectParamsT' :: OrderedField n => n -> Located (Trail V2 n) -> Located (Trail V2 n) -> ([n], [n])
- intersectParamsTS :: OrderedField n => Located (Trail V2 n) -> Located (Trail V2 n) -> ([[n]], [[n]])
- intersectParamsTS' :: OrderedField n => n -> Located (Trail V2 n) -> Located (Trail V2 n) -> ([[n]], [[n]])
- cutBy :: (OrderedField n, Real n, InSpace V2 n t, SameSpace t s, ToPath t, ToPath s) => t -> s -> [[Located (Trail V2 n)]]
- cutBy' :: (OrderedField n, Real n, InSpace V2 n t, SameSpace t s, ToPath t, ToPath s) => n -> t -> s -> [[Located (Trail V2 n)]]
- cutPBy :: (OrderedField n, Real n) => Path V2 n -> Path V2 n -> [[Located (Trail V2 n)]]
- cutPBy' :: (OrderedField n, Real n) => n -> Path V2 n -> Path V2 n -> [[Located (Trail V2 n)]]
- cutTBy :: (OrderedField n, Real n) => Located (Trail V2 n) -> Path V2 n -> [Located (Trail V2 n)]
- cutTBy' :: (OrderedField n, Real n) => n -> Located (Trail V2 n) -> Path V2 n -> [Located (Trail V2 n)]
- explodeSegments :: (Metric v, OrderedField n) => Path v n -> [[Located (Trail v n)]]
- explodeIntersections :: (OrderedField n, Real n) => Path V2 n -> [[Located (Trail V2 n)]]
- explodeIntersections' :: (OrderedField n, Real n) => n -> Path V2 n -> [[Located (Trail V2 n)]]
- explodeBoth :: (OrderedField n, Real n) => Path V2 n -> [[[Located (Trail V2 n)]]]
- explodeBoth' :: (OrderedField n, Real n) => n -> Path V2 n -> [[[Located (Trail V2 n)]]]
- class OnSections ps fs b n | ps b -> fs n, fs -> b n where
- onSections :: ps -> fs -> QDiagram b V2 n Any
Intersection Parameters
intersectParams :: (InSpace V2 n t, SameSpace t s, ToPath t, ToPath s, OrderedField n) => t -> s -> ([[n]], [[n]]) Source #
Find the intersect parameters for each component trail of two pathlike objects when the objects are intersected, returning a seperate list for each trail.
intersectParams' :: (InSpace V2 n t, SameSpace t s, ToPath t, ToPath s, OrderedField n) => n -> t -> s -> ([[n]], [[n]]) Source #
intersectParams using the given tolerance.
intersectParamsP :: OrderedField n => Path V2 n -> Path V2 n -> ([[n]], [[n]]) Source #
Find the intersect parameters for each component trail of two paths when the paths are intersected, returning a seperate list for each trail.
intersectParamsP' :: OrderedField n => n -> Path V2 n -> Path V2 n -> ([[n]], [[n]]) Source #
intersectParamsP using the given tolerance.
intersectParamsT :: OrderedField n => Located (Trail V2 n) -> Located (Trail V2 n) -> ([n], [n]) Source #
Find the intersect parameters between two located trails.
intersectParamsT' :: OrderedField n => n -> Located (Trail V2 n) -> Located (Trail V2 n) -> ([n], [n]) Source #
intersectParamsT using the given tolerance.
intersectParamsTS :: OrderedField n => Located (Trail V2 n) -> Located (Trail V2 n) -> ([[n]], [[n]]) Source #
Find the intersect parameters for each component segment of two located trails when the trails are intersected, returning a list for each trail containing a list of intersections for each segemnt of that trail.
intersectParamsTS' :: OrderedField n => n -> Located (Trail V2 n) -> Located (Trail V2 n) -> ([[n]], [[n]]) Source #
intersectParamsTS using the given tolerance.
Cutting Paths and Trails
cutBy :: (OrderedField n, Real n, InSpace V2 n t, SameSpace t s, ToPath t, ToPath s) => t -> s -> [[Located (Trail V2 n)]] Source #
Seperate a pathlike object into sections at every point it intersects a second pathlike object, returning a list of sections for each component trail.
cutByEx = onSections (squares `cutBy` line) colorLines
<> stroke line
where
squares, line :: Path V2 Double
squares = square 1
<> square 1 # rotate (1/8 @@ turn)
line = hrule 2
colorLines = map (map lc)
[ [ red, orange]
, [blue, purple] ]cutBy' :: (OrderedField n, Real n, InSpace V2 n t, SameSpace t s, ToPath t, ToPath s) => n -> t -> s -> [[Located (Trail V2 n)]] Source #
cutBy using the given tolerance for calculating intersections.
cutPBy :: (OrderedField n, Real n) => Path V2 n -> Path V2 n -> [[Located (Trail V2 n)]] Source #
Seperate a path into sections at every point it intersects a second path, returning a list of sections for each component trail.
cutPBy' :: (OrderedField n, Real n) => n -> Path V2 n -> Path V2 n -> [[Located (Trail V2 n)]] Source #
cutPBy using the given tolerance for calculating intersections.
cutTBy :: (OrderedField n, Real n) => Located (Trail V2 n) -> Path V2 n -> [Located (Trail V2 n)] Source #
Seperate a located trail into sections at every point it intersects a path.
cutTBy' :: (OrderedField n, Real n) => n -> Located (Trail V2 n) -> Path V2 n -> [Located (Trail V2 n)] Source #
cutTBy using the given tolerance for calculating intersections.
Rad Explosions
explodeSegments :: (Metric v, OrderedField n) => Path v n -> [[Located (Trail v n)]] Source #
explodePath specialized to return located trails. This provides the compiler
the necessary type information to use it with onSections without providing
a type annotation.
explodeSegmentsEx = onSections (explodeSegments squares) colorLines
where
squares = square 1
<> square 1 # rotate (1/8 @@ turn)
colorLines = map (map lc)
[ [ red, yellow, gold, orange]
, [blue, violet, purple, indigo] ]explodeIntersections :: (OrderedField n, Real n) => Path V2 n -> [[Located (Trail V2 n)]] Source #
Turn a path a list of component trails, then cut those segments at all their intersections.
explodeIntersectionsEx = onSections (explodeIntersections squares) colorLines
where
squares = square 1
<> square 1 # rotate (1/8 @@ turn)
colorLines = map (map lc)
[ [ gray, red, orange, yellow, green, blue, indigo, violet]
, [black, crimson, darkorange, gold, darkgreen, darkblue, midnightblue, darkviolet] ]explodeIntersections' :: (OrderedField n, Real n) => n -> Path V2 n -> [[Located (Trail V2 n)]] Source #
explodeIntersections using the given tolerance for calculating intersections.
explodeBoth :: (OrderedField n, Real n) => Path V2 n -> [[[Located (Trail V2 n)]]] Source #
Turn a path into a list of component segments for each component trail, then cut those segments at all their intersections.
explodeBothEx = onSections (explodeBoth squares) colorLines
where
squares = square 1
<> square 1 # rotate (1/8 @@ turn)
colorLines = map (map (map lc))
[ cycle [ [ gray, red, orange], [yellow, green, blue] ]
, cycle [ [black, crimson, darkorange], [ gold, darkgreen, darkblue] ] ]explodeBoth' :: (OrderedField n, Real n) => n -> Path V2 n -> [[[Located (Trail V2 n)]]] Source #
explodeBoth using the given tolerance for calculating intersections.
Consuming Cut Paths
class OnSections ps fs b n | ps b -> fs n, fs -> b n where Source #
Methods
onSections :: ps -> fs -> QDiagram b V2 n Any Source #
Zipply apply an arbitrarily nested list of attributes to the same shape of lists of pathlike objects, monoidally combining the results.
See examples for cutBy, explodeSegments, explodeIntersections, and explodeBoth.