Safe Haskell | None |
---|---|
Language | Haskell2010 |
- data LineSegment d p r
- pattern LineSegment :: forall d r p. EndPoint ((:+) (Point d r) p) -> EndPoint ((:+) (Point d r) p) -> LineSegment d p r
- pattern LineSegment' :: forall d r p. (:+) (Point d r) p -> (:+) (Point d r) p -> LineSegment d p r
- pattern ClosedLineSegment :: forall d r p. (:+) (Point d r) p -> (:+) (Point d r) p -> LineSegment d p r
- _SubLine :: (Fractional r, Eq r, Arity d) => Iso' (LineSegment d p r) (SubLine d p r)
- module Data.Geometry.Interval
- toLineSegment :: (Monoid p, Num r, Arity d) => Line d r -> LineSegment d p r
- onSegment :: (Ord r, Fractional r, Arity d) => Point d r -> LineSegment d p r -> Bool
- orderedEndPoints :: Ord r => LineSegment 2 p r -> (Point 2 r :+ p, Point 2 r :+ p)
- segmentLength :: (Arity d, Floating r) => LineSegment d p r -> r
- sqDistanceToSeg :: (Arity d, Fractional r, Ord r) => Point d r -> LineSegment d p r -> r
- sqDistanceToSegArg :: (Arity d, Fractional r, Ord r) => Point d r -> LineSegment d p r -> (r, Point d r)
- flipSegment :: LineSegment d p r -> LineSegment d p r
Documentation
data LineSegment d p r Source #
Line segments. LineSegments have a start and end point, both of which may contain additional data of type p. We can think of a Line-Segment being defined as
data LineSegment d p r = LineSegment (EndPoint (Point d r :+ p)) (EndPoint (Point d r :+ p))
pattern LineSegment :: forall d r p. EndPoint ((:+) (Point d r) p) -> EndPoint ((:+) (Point d r) p) -> LineSegment d p r Source #
Pattern that essentially models the line segment as a:
data LineSegment d p r = LineSegment (EndPoint (Point d r :+ p)) (EndPoint (Point d r :+ p))
pattern LineSegment' :: forall d r p. (:+) (Point d r) p -> (:+) (Point d r) p -> LineSegment d p r Source #
Gets the start and end point, but forgetting if they are open or closed.
pattern ClosedLineSegment :: forall d r p. (:+) (Point d r) p -> (:+) (Point d r) p -> LineSegment d p r Source #
_SubLine :: (Fractional r, Eq r, Arity d) => Iso' (LineSegment d p r) (SubLine d p r) Source #
module Data.Geometry.Interval
toLineSegment :: (Monoid p, Num r, Arity d) => Line d r -> LineSegment d p r Source #
Directly convert a line into a line segment.
onSegment :: (Ord r, Fractional r, Arity d) => Point d r -> LineSegment d p r -> Bool Source #
Test if a point lies on a line segment.
>>>
(point2 1 0) `onSegment` (ClosedLineSegment (origin :+ ()) (point2 2 0 :+ ()))
True>>>
(point2 1 1) `onSegment` (ClosedLineSegment (origin :+ ()) (point2 2 0 :+ ()))
False>>>
(point2 5 0) `onSegment` (ClosedLineSegment (origin :+ ()) (point2 2 0 :+ ()))
False>>>
(point2 (-1) 0) `onSegment` (ClosedLineSegment (origin :+ ()) (point2 2 0 :+ ()))
False>>>
(point2 1 1) `onSegment` (ClosedLineSegment (origin :+ ()) (point2 3 3 :+ ()))
True
Note that the segments are assumed to be closed. So the end points lie on the segment.
>>>
(point2 2 0) `onSegment` (ClosedLineSegment (origin :+ ()) (point2 2 0 :+ ()))
True>>>
origin `onSegment` (ClosedLineSegment (origin :+ ()) (point2 2 0 :+ ()))
True
This function works for arbitrary dimensons.
>>>
(point3 1 1 1) `onSegment` (ClosedLineSegment (origin :+ ()) (point3 3 3 3 :+ ()))
True>>>
(point3 1 2 1) `onSegment` (ClosedLineSegment (origin :+ ()) (point3 3 3 3 :+ ()))
False
orderedEndPoints :: Ord r => LineSegment 2 p r -> (Point 2 r :+ p, Point 2 r :+ p) Source #
The left and right end point (or left below right if they have equal x-coords)
segmentLength :: (Arity d, Floating r) => LineSegment d p r -> r Source #
Length of the line segment
sqDistanceToSeg :: (Arity d, Fractional r, Ord r) => Point d r -> LineSegment d p r -> r Source #
Squared distance from the point to the Segment s. The same remark as for
the sqDistanceToSegArg
applies here.
sqDistanceToSegArg :: (Arity d, Fractional r, Ord r) => Point d r -> LineSegment d p r -> (r, Point d r) Source #
Squared distance from the point to the Segment s, and the point on s realizing it. Note that if the segment is *open*, the closest point returned may be one of the (open) end points, even though technically the end point does not lie on the segment. (The true closest point then lies arbitrarily close to the end point).
flipSegment :: LineSegment d p r -> LineSegment d p r Source #
flips the start and end point of the segment