Copyright | (c) Frank Staals |
---|---|
License | See LICENCE file |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- data LineSegment d p r
- pattern LineSegment :: EndPoint (Point d r :+ p) -> EndPoint (Point d r :+ p) -> LineSegment d p r
- pattern LineSegment' :: (Point d r :+ p) -> (Point d r :+ p) -> LineSegment d p r
- pattern ClosedLineSegment :: (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)
- data Range a = Range {}
- data EndPoint a
- unEndPoint :: Lens (EndPoint a) (EndPoint b) a b
- isOpen :: EndPoint a -> Bool
- isClosed :: EndPoint a -> Bool
- pattern Range' :: a -> a -> Range a
- pattern ClosedRange :: a -> a -> Range a
- pattern OpenRange :: a -> a -> Range a
- lower :: forall a. Lens' (Range a) (EndPoint a)
- upper :: forall a. Lens' (Range a) (EndPoint a)
- prettyShow :: Show a => Range a -> String
- inRange :: Ord a => a -> Range a -> Bool
- clipLower :: Ord a => EndPoint a -> Range a -> Maybe (Range a)
- clipUpper :: Ord a => EndPoint a -> Range a -> Maybe (Range a)
- covers :: Ord a => Range a -> Range a -> Bool
- isValid :: Ord a => Range a -> Bool
- shiftLeft :: Num r => r -> Range r -> Range r
- shiftRight :: Num r => r -> Range r -> Range r
- newtype Interval a r = GInterval {
- _unInterval :: Range (r :+ a)
- class HasEnd t where
- class HasStart t where
- type StartCore t
- type StartExtra t
- pattern Interval :: EndPoint (r :+ a) -> EndPoint (r :+ a) -> Interval a r
- pattern ClosedInterval :: (r :+ a) -> (r :+ a) -> Interval a r
- pattern OpenInterval :: (r :+ a) -> (r :+ a) -> Interval a r
- inInterval :: Ord r => r -> Interval a r -> Bool
- shiftLeft' :: Num r => r -> Interval a r -> Interval a r
- 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))
Instances
pattern LineSegment :: 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' :: (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 :: (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 #
Data type for representing ranges.
Instances
Endpoints of a range may either be open or closed.
Instances
pattern Range' :: a -> a -> Range a Source #
A range from l to u, ignoring/forgetting the type of the endpoints
pattern ClosedRange :: a -> a -> Range a Source #
inRange :: Ord a => a -> Range a -> Bool Source #
Test if a value lies in a range.
>>>
1 `inRange` (OpenRange 0 2)
True>>>
1 `inRange` (OpenRange 0 1)
False>>>
1 `inRange` (ClosedRange 0 1)
True>>>
1 `inRange` (ClosedRange 1 1)
True>>>
10 `inRange` (OpenRange 1 10)
False>>>
10 `inRange` (ClosedRange 0 1)
False
clipLower :: Ord a => EndPoint a -> Range a -> Maybe (Range a) Source #
Clip the interval from below. I.e. intersect with the interval {l,infty), where { is either open, (, orr closed, [.
clipUpper :: Ord a => EndPoint a -> Range a -> Maybe (Range a) Source #
Clip the interval from above. I.e. intersect with (-infty, u}, where } is either open, ), or closed, ],
covers :: Ord a => Range a -> Range a -> Bool Source #
Wether or not the first range completely covers the second one
isValid :: Ord a => Range a -> Bool Source #
Check if the range is valid and nonEmpty, i.e. if the lower endpoint is indeed smaller than the right endpoint. Note that we treat empty open-ranges as invalid as well.
shiftLeft :: Num r => r -> Range r -> Range r Source #
Shift a range x units to the left
>>>
prettyShow $ shiftLeft 10 (ClosedRange 10 20)
"[0, 10]">>>
prettyShow $ shiftLeft 10 (OpenRange 15 25)
"(5, 15)"
shiftRight :: Num r => r -> Range r -> Range r Source #
Shifts the range to the right
>>>
prettyShow $ shiftRight 10 (ClosedRange 10 20)
"[20, 30]">>>
prettyShow $ shiftRight 10 (OpenRange 15 25)
"(25, 35)"
An Interval is essentially a Range
but with possible payload
GInterval | |
|
Instances
Instances
HasEnd (Interval a r) Source # | |
HasEnd (LineSegment d p r) Source # | |
Defined in Data.Geometry.LineSegment type EndCore (LineSegment d p r) :: * Source # type EndExtra (LineSegment d p r) :: * Source # end :: Lens' (LineSegment d p r) (EndCore (LineSegment d p r) :+ EndExtra (LineSegment d p r)) Source # |
class HasStart t where Source #
Instances
HasStart (Interval a r) Source # | |
HasStart (HalfLine d r) Source # | |
HasStart (LineSegment d p r) Source # | |
Defined in Data.Geometry.LineSegment type StartCore (LineSegment d p r) :: * Source # type StartExtra (LineSegment d p r) :: * Source # start :: Lens' (LineSegment d p r) (StartCore (LineSegment d p r) :+ StartExtra (LineSegment d p r)) Source # |
inInterval :: Ord r => r -> Interval a r -> Bool Source #
Test if a value lies in an interval. Note that the difference between inInterval and inRange is that the extra value is *not* used in the comparison with inInterval, whereas it is in inRange.
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