hgeometry-0.14: Geometric Algorithms, Data structures, and Data types.
Copyright(C) Frank Staals
Licensesee the LICENSE file
MaintainerFrank Staals
Safe HaskellNone
LanguageHaskell2010

Algorithms.Geometry.LineSegmentIntersection

Description

 
Synopsis

Documentation

hasIntersections :: (Ord r, Num r) => [LineSegment 2 p r :+ e] -> Bool Source #

Tests if there are any intersections.

\(O(n\log n)\)

intersections :: forall p r e. (Ord r, Fractional r) => [LineSegment 2 p r :+ e] -> Intersections p r e 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 :+ e] -> Intersections p r e 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.

type Intersections p r e = Map (Point 2 r) (Associated p r e) Source #

For each intersection point the segments intersecting there.

data Associated p r e Source #

The line segments that contain a given point p may either have p as the endpoint or have p in their interior.

if somehow the segment is degenerate, and p is both the start and end it is reported only as the start point.

Constructors

Associated 

Fields

Instances

Instances details
Functor (Associated p r) Source # 
Instance details

Defined in Algorithms.Geometry.LineSegmentIntersection.Types

Methods

fmap :: (a -> b) -> Associated p r a -> Associated p r b #

(<$) :: a -> Associated p r b -> Associated p r a #

Eq r => Eq (Associated p r e) Source # 
Instance details

Defined in Algorithms.Geometry.LineSegmentIntersection.Types

Methods

(==) :: Associated p r e -> Associated p r e -> Bool #

(/=) :: Associated p r e -> Associated p r e -> Bool #

(Read r, Read p, Read e, Ord r, Fractional r) => Read (Associated p r e) Source # 
Instance details

Defined in Algorithms.Geometry.LineSegmentIntersection.Types

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

Defined in Algorithms.Geometry.LineSegmentIntersection.Types

Methods

showsPrec :: Int -> Associated p r e -> ShowS #

show :: Associated p r e -> String #

showList :: [Associated p r e] -> ShowS #

Generic (Associated p r e) Source # 
Instance details

Defined in Algorithms.Geometry.LineSegmentIntersection.Types

Associated Types

type Rep (Associated p r e) :: Type -> Type #

Methods

from :: Associated p r e -> Rep (Associated p r e) x #

to :: Rep (Associated p r e) x -> Associated p r e #

(Ord r, Fractional r) => Semigroup (Associated p r e) Source # 
Instance details

Defined in Algorithms.Geometry.LineSegmentIntersection.Types

Methods

(<>) :: Associated p r e -> Associated p r e -> Associated p r e #

sconcat :: NonEmpty (Associated p r e) -> Associated p r e #

stimes :: Integral b => b -> Associated p r e -> Associated p r e #

(Ord r, Fractional r) => Monoid (Associated p r e) Source # 
Instance details

Defined in Algorithms.Geometry.LineSegmentIntersection.Types

Methods

mempty :: Associated p r e #

mappend :: Associated p r e -> Associated p r e -> Associated p r e #

mconcat :: [Associated p r e] -> Associated p r e #

(NFData p, NFData r, NFData e) => NFData (Associated p r e) Source # 
Instance details

Defined in Algorithms.Geometry.LineSegmentIntersection.Types

Methods

rnf :: Associated p r e -> () #

type Rep (Associated p r e) Source # 
Instance details

Defined in Algorithms.Geometry.LineSegmentIntersection.Types

type Rep (Associated p r e)

data IntersectionPoint p r e Source #

An intersection point together with all segments intersecting at this point.

Constructors

IntersectionPoint 

Fields

Instances

Instances details
Functor (IntersectionPoint p r) Source # 
Instance details

Defined in Algorithms.Geometry.LineSegmentIntersection.Types

Methods

fmap :: (a -> b) -> IntersectionPoint p r a -> IntersectionPoint p r b #

(<$) :: a -> IntersectionPoint p r b -> IntersectionPoint p r a #

Eq r => Eq (IntersectionPoint p r e) Source # 
Instance details

Defined in Algorithms.Geometry.LineSegmentIntersection.Types

(Read r, Read p, Read e, Ord r, Fractional r) => Read (IntersectionPoint p r e) Source # 
Instance details

Defined in Algorithms.Geometry.LineSegmentIntersection.Types

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

Defined in Algorithms.Geometry.LineSegmentIntersection.Types

Generic (IntersectionPoint p r e) Source # 
Instance details

Defined in Algorithms.Geometry.LineSegmentIntersection.Types

Associated Types

type Rep (IntersectionPoint p r e) :: Type -> Type #

Methods

from :: IntersectionPoint p r e -> Rep (IntersectionPoint p r e) x #

to :: Rep (IntersectionPoint p r e) x -> IntersectionPoint p r e #

(NFData p, NFData r, NFData e) => NFData (IntersectionPoint p r e) Source # 
Instance details

Defined in Algorithms.Geometry.LineSegmentIntersection.Types

Methods

rnf :: IntersectionPoint p r e -> () #

type Rep (IntersectionPoint p r e) Source # 
Instance details

Defined in Algorithms.Geometry.LineSegmentIntersection.Types

type Rep (IntersectionPoint p r e) = D1 ('MetaData "IntersectionPoint" "Algorithms.Geometry.LineSegmentIntersection.Types" "hgeometry-0.14-BBhGh1sNn85H5mfsjBn14s" 'False) (C1 ('MetaCons "IntersectionPoint" 'PrefixI 'True) (S1 ('MetaSel ('Just "_intersectionPoint") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Point 2 r)) :*: S1 ('MetaSel ('Just "_associatedSegs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Associated p r e))))

mkIntersectionPoint Source #

Arguments

:: (Ord r, Fractional r) 
=> Point 2 r 
-> [LineSegment 2 p r :+ e]

uncategorized

-> [LineSegment 2 p r :+ e]

segments we know contain p,

-> IntersectionPoint p r e 

Given a point p, and a bunch of segments that suposedly intersect at p, correctly categorize them.

hasSelfIntersections :: (Ord r, Fractional r) => Polygon t p r -> Bool Source #

Test if the polygon has self intersections.

\(O(n \log n)\)