Copyright | (C) Frank Staals |
---|---|
License | see the LICENSE file |
Maintainer | Frank Staals |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- data VerticalRayShootingStructure p e r = VerticalRayShootingStructure r (Vector (r :+ StatusStructure p e r))
- type StatusStructure p e r = Set (LineSegment 2 p r :+ e)
- leftMost :: forall p e r. Getter (VerticalRayShootingStructure p e r) r
- sweepStruct :: forall p e r. Getter (VerticalRayShootingStructure p e r) (Vector ((:+) r (StatusStructure p e r)))
- verticalRayShootingStructure :: (Ord r, Fractional r, Foldable1 t) => t (LineSegment 2 p r :+ e) -> VerticalRayShootingStructure p e r
- segmentAbove :: (Ord r, Num r) => Point 2 r -> VerticalRayShootingStructure p e r -> Maybe (LineSegment 2 p r :+ e)
- segmentAboveOrOn :: (Ord r, Num r) => Point 2 r -> VerticalRayShootingStructure p e r -> Maybe (LineSegment 2 p r :+ e)
- findSlab :: Ord r => Point 2 r -> VerticalRayShootingStructure p e r -> Maybe (StatusStructure p e r)
- lookupAbove :: (Ord r, Num r) => Point 2 r -> StatusStructure p e r -> Maybe (LineSegment 2 p r :+ e)
- lookupAboveOrOn :: (Ord r, Num r) => Point 2 r -> StatusStructure p e r -> Maybe (LineSegment 2 p r :+ e)
- searchInSlab :: Num r => (Line 2 r -> Bool) -> StatusStructure p e r -> Maybe (LineSegment 2 p r :+ e)
- ordAt :: (Fractional r, Ord r) => r -> Compare (LineSegment 2 p r :+ e)
- yCoordAt :: (Fractional r, Ord r) => r -> (LineSegment 2 p r :+ e) -> r
Documentation
data VerticalRayShootingStructure p e r Source #
The vertical ray shooting data structure
VerticalRayShootingStructure r (Vector (r :+ StatusStructure p e r)) |
Instances
(Eq r, Eq p, Eq e) => Eq (VerticalRayShootingStructure p e r) Source # | |
Defined in Data.Geometry.VerticalRayShooting.PersistentSweep (==) :: VerticalRayShootingStructure p e r -> VerticalRayShootingStructure p e r -> Bool # (/=) :: VerticalRayShootingStructure p e r -> VerticalRayShootingStructure p e r -> Bool # | |
(Show r, Show p, Show e) => Show (VerticalRayShootingStructure p e r) Source # | |
Defined in Data.Geometry.VerticalRayShooting.PersistentSweep showsPrec :: Int -> VerticalRayShootingStructure p e r -> ShowS # show :: VerticalRayShootingStructure p e r -> String # showList :: [VerticalRayShootingStructure p e r] -> ShowS # |
type StatusStructure p e r = Set (LineSegment 2 p r :+ e) Source #
leftMost :: forall p e r. Getter (VerticalRayShootingStructure p e r) r Source #
sweepStruct :: forall p e r. Getter (VerticalRayShootingStructure p e r) (Vector ((:+) r (StatusStructure p e r))) Source #
Building the Data Structure
verticalRayShootingStructure :: (Ord r, Fractional r, Foldable1 t) => t (LineSegment 2 p r :+ e) -> VerticalRayShootingStructure p e r Source #
Given a set of \(n\) interiorly pairwise disjoint *closed* segments, compute a vertical ray shooting data structure. (i.e. the endpoints of the segments may coincide).
pre: no vertical segments
running time: \(O(n\log n)\). space: \(O(n\log n)\).
Querying the Data Structure
segmentAbove :: (Ord r, Num r) => Point 2 r -> VerticalRayShootingStructure p e r -> Maybe (LineSegment 2 p r :+ e) Source #
Find the segment vertically strictly above query point q, if it exists.
\(O(\log n)\)
segmentAboveOrOn :: (Ord r, Num r) => Point 2 r -> VerticalRayShootingStructure p e r -> Maybe (LineSegment 2 p r :+ e) Source #
Find the segment vertically query point q, if it exists.
\(O(\log n)\)
findSlab :: Ord r => Point 2 r -> VerticalRayShootingStructure p e r -> Maybe (StatusStructure p e r) Source #
Given a query point, find the (data structure of the) slab containing the query point
\(O(\log n)\)
lookupAbove :: (Ord r, Num r) => Point 2 r -> StatusStructure p e r -> Maybe (LineSegment 2 p r :+ e) Source #
Finds the first segment strictly above q
\(O(\log n)\)
lookupAboveOrOn :: (Ord r, Num r) => Point 2 r -> StatusStructure p e r -> Maybe (LineSegment 2 p r :+ e) Source #
Finds the segment containing or above the query point q
\(O(\log n)\)
searchInSlab :: Num r => (Line 2 r -> Bool) -> StatusStructure p e r -> Maybe (LineSegment 2 p r :+ e) Source #
generic searching function
ordAt :: (Fractional r, Ord r) => r -> Compare (LineSegment 2 p r :+ e) Source #
Compare based on the y-coordinate of the intersection with the horizontal line through y
yCoordAt :: (Fractional r, Ord r) => r -> (LineSegment 2 p r :+ e) -> r Source #
Given an x-coordinate and a line segment that intersects the vertical line through x, compute the y-coordinate of this intersection point.
note that we will pretend that the line segment is closed, even if it is not