hgeometry-0.12.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

Description

 
Synopsis

Documentation

hasInteriorIntersections :: (Ord r, Fractional r) => [LineSegment 2 p r] -> Bool Source #

\(O(n \log n)\)

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

\(O(n \log n)\)

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

data Associated p r Source #

Constructors

Associated 

Fields

Instances

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

Defined in Algorithms.Geometry.LineSegmentIntersection.Types

Methods

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

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

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

Defined in Algorithms.Geometry.LineSegmentIntersection.Types

Methods

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

show :: Associated p r -> String #

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

Generic (Associated p r) Source # 
Instance details

Defined in Algorithms.Geometry.LineSegmentIntersection.Types

Associated Types

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

Methods

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

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

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

Defined in Algorithms.Geometry.LineSegmentIntersection.Types

Methods

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

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

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

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

Defined in Algorithms.Geometry.LineSegmentIntersection.Types

Methods

mempty :: Associated p r #

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

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

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

Defined in Algorithms.Geometry.LineSegmentIntersection.Types

Methods

rnf :: Associated p r -> () #

type Rep (Associated p r) Source # 
Instance details

Defined in Algorithms.Geometry.LineSegmentIntersection.Types

type Rep (Associated p r)

isEndPointIntersection :: Associated p r -> Bool Source #

reports true if there is at least one segment for which this intersection point is interior.

\(O(1)\)

associated :: Ord r => [LineSegment 2 p r] -> [LineSegment 2 p r] -> Associated p r Source #

type Compare a = a -> a -> Ordering Source #