Copyright | (C) Frank Staals |
---|---|
License | see the LICENSE file |
Maintainer | Frank Staals |
Safe Haskell | None |
Language | Haskell2010 |
The \(O((n+k)\log n)\) time line segment intersection algorithm by Bentley and Ottmann.
Synopsis
- intersections :: (Ord r, Fractional r) => [LineSegment 2 p r] -> Intersections p r
- interiorIntersections :: (Ord r, Fractional r) => [LineSegment 2 p r] -> Intersections p r
- asEventPts :: Ord r => LineSegment 2 p r -> [Event p r]
- merge :: Ord r => [IntersectionPoint p r] -> Intersections p r
- groupStarts :: Eq r => [Event p r] -> [Event p r]
- data EventType s
- = Start !(NonEmpty s)
- | Intersection
- | End !s
- data Event p r = Event {
- eventPoint :: !(Point 2 r)
- eventType :: !(EventType (LineSegment 2 p r))
- ordPoints :: Ord r => Point 2 r -> Point 2 r -> Ordering
- startSegs :: Event p r -> [LineSegment 2 p r]
- ordAt :: (Fractional r, Ord r) => r -> Compare (LineSegment 2 p r)
- xCoordAt :: (Fractional r, Ord r) => r -> LineSegment 2 p r -> r
- type EventQueue p r = Set (Event p r)
- type StatusStructure p r = Set (LineSegment 2 p r)
- sweep :: (Ord r, Fractional r) => EventQueue p r -> StatusStructure p r -> [IntersectionPoint p r]
- isClosedStart :: Eq r => Point 2 r -> LineSegment 2 p r -> Bool
- handle :: forall r p. (Ord r, Fractional r) => Event p r -> EventQueue p r -> StatusStructure p r -> [IntersectionPoint p r]
- extractContains :: (Fractional r, Ord r) => Point 2 r -> StatusStructure p r -> (StatusStructure p r, [LineSegment 2 p r], StatusStructure p r)
- toStatusStruct :: (Fractional r, Ord r) => Point 2 r -> [LineSegment 2 p r] -> StatusStructure p r
- rightEndpoint :: Ord r => LineSegment 2 p r -> r
- endsAt :: Ord r => Point 2 r -> LineSegment 2 p r -> Bool
- findNewEvent :: (Ord r, Fractional r) => Point 2 r -> LineSegment 2 p r -> LineSegment 2 p r -> Maybe (Event p r)
Documentation
intersections :: (Ord r, Fractional r) => [LineSegment 2 p r] -> Intersections p r Source #
Compute all intersections
\(O((n+k)\log n)\), where \(k\) is the number of intersections.
interiorIntersections :: (Ord r, Fractional r) => [LineSegment 2 p r] -> Intersections p r Source #
Computes all intersection points p s.t. p lies in the interior of at least one of the segments.
\(O((n+k)\log n)\), where \(k\) is the number of intersections.
asEventPts :: Ord r => LineSegment 2 p r -> [Event p r] Source #
Computes the event points for a given line segment
merge :: Ord r => [IntersectionPoint p r] -> Intersections p r Source #
Group the segments with the intersection points
groupStarts :: Eq r => [Event p r] -> [Event p r] Source #
Group the startpoints such that segments with the same start point correspond to one event.
Data type for Events
Type of segment
Start !(NonEmpty s) | |
Intersection | |
End !s |
Instances
Eq (EventType s) Source # | |
Ord (EventType s) Source # | |
Defined in Algorithms.Geometry.LineSegmentIntersection.BentleyOttmann | |
Show s => Show (EventType s) Source # | |
The actual event consists of a point and its type
Event | |
|
ordPoints :: Ord r => Point 2 r -> Point 2 r -> Ordering Source #
An ordering that is decreasing on y, increasing on x
startSegs :: Event p r -> [LineSegment 2 p r] Source #
Get the segments that start at the given event point
ordAt :: (Fractional r, Ord r) => r -> Compare (LineSegment 2 p r) Source #
Compare based on the x-coordinate of the intersection with the horizontal line through y
xCoordAt :: (Fractional r, Ord r) => r -> LineSegment 2 p r -> r Source #
Given a y coord and a line segment that intersects the horizontal line through y, compute the x-coordinate of this intersection point.
note that we will pretend that the line segment is closed, even if it is not
The Main Sweep
type EventQueue p r = Set (Event p r) Source #
type StatusStructure p r = Set (LineSegment 2 p r) Source #
sweep :: (Ord r, Fractional r) => EventQueue p r -> StatusStructure p r -> [IntersectionPoint p r] Source #
Run the sweep handling all events
isClosedStart :: Eq r => Point 2 r -> LineSegment 2 p r -> Bool Source #
handle :: forall r p. (Ord r, Fractional r) => Event p r -> EventQueue p r -> StatusStructure p r -> [IntersectionPoint p r] Source #
Handle an event point
extractContains :: (Fractional r, Ord r) => Point 2 r -> StatusStructure p r -> (StatusStructure p r, [LineSegment 2 p r], StatusStructure p r) Source #
split the status structure, extracting the segments that contain p. the result is (before,contains,after)
toStatusStruct :: (Fractional r, Ord r) => Point 2 r -> [LineSegment 2 p r] -> StatusStructure p r Source #
Given a point and the linesegements that contain it. Create a piece of status structure for it.
rightEndpoint :: Ord r => LineSegment 2 p r -> r Source #
Get the right endpoint of a segment
Finding New events
findNewEvent :: (Ord r, Fractional r) => Point 2 r -> LineSegment 2 p r -> LineSegment 2 p r -> Maybe (Event p r) Source #
Find all events