hgeometry-0.10.0.0: Geometric Algorithms, Data structures, and Data types.

Copyright(C) Frank Staals
Licensesee the LICENSE file
MaintainerFrank Staals
Safe HaskellNone
LanguageHaskell2010

Algorithms.Geometry.LineSegmentIntersection.BentleyOttmann

Contents

Description

The \(O((n+k)\log n)\) time line segment intersection algorithm by Bentley and Ottmann.

Synopsis

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

data Event p r Source #

The actual event consists of a point and its type

Constructors

Event 

Fields

Instances
Eq r => Eq (Event p r) Source # 
Instance details

Defined in Algorithms.Geometry.LineSegmentIntersection.BentleyOttmann

Methods

(==) :: Event p r -> Event p r -> Bool #

(/=) :: Event p r -> Event p r -> Bool #

Ord r => Ord (Event p r) Source # 
Instance details

Defined in Algorithms.Geometry.LineSegmentIntersection.BentleyOttmann

Methods

compare :: Event p r -> Event p r -> Ordering #

(<) :: Event p r -> Event p r -> Bool #

(<=) :: Event p r -> Event p r -> Bool #

(>) :: Event p r -> Event p r -> Bool #

(>=) :: Event p r -> Event p r -> Bool #

max :: Event p r -> Event p r -> Event p r #

min :: Event p r -> Event p r -> Event p r #

(Show r, Show p) => Show (Event p r) Source # 
Instance details

Defined in Algorithms.Geometry.LineSegmentIntersection.BentleyOttmann

Methods

showsPrec :: Int -> Event p r -> ShowS #

show :: Event p r -> String #

showList :: [Event p r] -> ShowS #

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 #

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

endsAt :: Ord r => Point 2 r -> LineSegment 2 p r -> Bool Source #

Test if a segment ends at p

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