Copyright | (C) Frank Staals |
---|---|
License | see the LICENSE file |
Maintainer | Frank Staals |
Safe Haskell | None |
Language | Haskell2010 |
\(d\)-dimensional lines.
Synopsis
- data Line d r = Line {
- _anchorPoint :: !(Point d r)
- _direction :: !(Vector d r)
- direction :: forall d r. Lens' (Line d r) (Vector d r)
- anchorPoint :: forall d r. Lens' (Line d r) (Point d r)
- lineThrough :: (Num r, Arity d) => Point d r -> Point d r -> Line d r
- verticalLine :: Num r => r -> Line 2 r
- horizontalLine :: Num r => r -> Line 2 r
- perpendicularTo :: Num r => Line 2 r -> Line 2 r
- isPerpendicularTo :: (Num r, Eq r) => Vector 2 r -> Line 2 r -> Bool
- isIdenticalTo :: (Eq r, Arity d) => Line d r -> Line d r -> Bool
- isParallelTo :: (Eq r, Fractional r, Arity d) => Line d r -> Line d r -> Bool
- onLine :: (Eq r, Fractional r, Arity d) => Point d r -> Line d r -> Bool
- onLine2 :: (Ord r, Num r) => Point 2 r -> Line 2 r -> Bool
- pointAt :: (Num r, Arity d) => r -> Line d r -> Point d r
- toOffset :: (Eq r, Fractional r, Arity d) => Point d r -> Line d r -> Maybe r
- toOffset' :: (Eq r, Fractional r, Arity d) => Point d r -> Line d r -> r
- sqDistanceTo :: (Fractional r, Arity d) => Point d r -> Line d r -> r
- sqDistanceToArg :: (Fractional r, Arity d) => Point d r -> Line d r -> (r, Point d r)
- class HasSupportingLine t where
- supportingLine :: t -> Line (Dimension t) (NumType t)
- fromLinearFunction :: Num r => r -> r -> Line 2 r
- toLinearFunction :: forall r. (Fractional r, Eq r) => Line 2 r -> Maybe (r, r)
- data SideTestUpDown
- onSideUpDown :: (Ord r, Num r) => Point 2 r -> Line 2 r -> SideTestUpDown
- data SideTest
- onSide :: (Ord r, Num r) => Point 2 r -> Line 2 r -> SideTest
- liesAbove :: (Ord r, Num r) => Point 2 r -> Line 2 r -> Bool
- bisector :: Fractional r => Point 2 r -> Point 2 r -> Line 2 r
- cmpSlope :: (Num r, Ord r) => Line 2 r -> Line 2 r -> Ordering
d-dimensional Lines
A line is given by an anchor point and a vector indicating the direction.
Line | |
|
Instances
Functions on lines
lineThrough :: (Num r, Arity d) => Point d r -> Point d r -> Line d r Source #
A line may be constructed from two points.
verticalLine :: Num r => r -> Line 2 r Source #
horizontalLine :: Num r => r -> Line 2 r Source #
perpendicularTo :: Num r => Line 2 r -> Line 2 r Source #
Given a line l with anchor point p and vector v, get the line perpendicular to l that also goes through p. The resulting line m is oriented such that v points into the left halfplane of m.
>>>
perpendicularTo $ Line (Point2 3 4) (Vector2 (-1) 2)
Line (Point2 [3,4]) (Vector2 [-2,-1])
isPerpendicularTo :: (Num r, Eq r) => Vector 2 r -> Line 2 r -> Bool Source #
Test if a vector is perpendicular to the line.
isIdenticalTo :: (Eq r, Arity d) => Line d r -> Line d r -> Bool Source #
Test if two lines are identical, meaning; if they have exactly the same anchor point and directional vector.
isParallelTo :: (Eq r, Fractional r, Arity d) => Line d r -> Line d r -> Bool Source #
Test if the two lines are parallel.
>>>
lineThrough origin (Point2 1 0) `isParallelTo` lineThrough (Point2 1 1) (Point2 2 1)
True>>>
lineThrough origin (Point2 1 0) `isParallelTo` lineThrough (Point2 1 1) (Point2 2 2)
False
onLine :: (Eq r, Fractional r, Arity d) => Point d r -> Line d r -> Bool Source #
Test if point p lies on line l
>>>
origin `onLine` lineThrough origin (Point2 1 0)
True>>>
Point2 10 10 `onLine` lineThrough origin (Point2 2 2)
True>>>
Point2 10 5 `onLine` lineThrough origin (Point2 2 2)
False
onLine2 :: (Ord r, Num r) => Point 2 r -> Line 2 r -> Bool Source #
Specific 2d version of testing if apoint lies on a line.
pointAt :: (Num r, Arity d) => r -> Line d r -> Point d r Source #
Get the point at the given position along line, where 0 corresponds to the anchorPoint of the line, and 1 to the point anchorPoint .+^ directionVector
toOffset :: (Eq r, Fractional r, Arity d) => Point d r -> Line d r -> Maybe r Source #
Given point p and a line (Line q v), Get the scalar lambda s.t. p = q + lambda v. If p does not lie on the line this returns a Nothing.
toOffset' :: (Eq r, Fractional r, Arity d) => Point d r -> Line d r -> r Source #
Given point p *on* a line (Line q v), Get the scalar lambda s.t.
p = q + lambda v. (So this is an unsafe version of toOffset
)
pre: the input point p lies on the line l.
sqDistanceTo :: (Fractional r, Arity d) => Point d r -> Line d r -> r Source #
Squared distance from point p to line l
sqDistanceToArg :: (Fractional r, Arity d) => Point d r -> Line d r -> (r, Point d r) Source #
The squared distance between the point p and the line l, and the point m realizing this distance.
Supporting Lines
class HasSupportingLine t where Source #
Types for which we can compute a supporting line, i.e. a line that contains the thing of type t.
Instances
HasSupportingLine (Line d r) Source # | |
Defined in Data.Geometry.Line.Internal | |
HasSupportingLine (HalfLine d r) Source # | |
Defined in Data.Geometry.HalfLine | |
(Num r, Arity d) => HasSupportingLine (LineSegment d p r) Source # | |
Defined in Data.Geometry.LineSegment supportingLine :: LineSegment d p r -> Line (Dimension (LineSegment d p r)) (NumType (LineSegment d p r)) Source # |
Convenience functions on Two dimensional lines
fromLinearFunction :: Num r => r -> r -> Line 2 r Source #
Create a line from the linear function ax + b
toLinearFunction :: forall r. (Fractional r, Eq r) => Line 2 r -> Maybe (r, r) Source #
get values a,b s.t. the input line is described by y = ax + b. returns Nothing if the line is vertical
data SideTestUpDown Source #
Result of a side test
Instances
Eq SideTestUpDown Source # | |
Defined in Data.Geometry.Line.Internal (==) :: SideTestUpDown -> SideTestUpDown -> Bool # (/=) :: SideTestUpDown -> SideTestUpDown -> Bool # | |
Ord SideTestUpDown Source # | |
Defined in Data.Geometry.Line.Internal compare :: SideTestUpDown -> SideTestUpDown -> Ordering # (<) :: SideTestUpDown -> SideTestUpDown -> Bool # (<=) :: SideTestUpDown -> SideTestUpDown -> Bool # (>) :: SideTestUpDown -> SideTestUpDown -> Bool # (>=) :: SideTestUpDown -> SideTestUpDown -> Bool # max :: SideTestUpDown -> SideTestUpDown -> SideTestUpDown # min :: SideTestUpDown -> SideTestUpDown -> SideTestUpDown # | |
Read SideTestUpDown Source # | |
Defined in Data.Geometry.Line.Internal readsPrec :: Int -> ReadS SideTestUpDown # readList :: ReadS [SideTestUpDown] # | |
Show SideTestUpDown Source # | |
Defined in Data.Geometry.Line.Internal showsPrec :: Int -> SideTestUpDown -> ShowS # show :: SideTestUpDown -> String # showList :: [SideTestUpDown] -> ShowS # |
onSideUpDown :: (Ord r, Num r) => Point 2 r -> Line 2 r -> SideTestUpDown Source #
Given a point q and a line l, compute to which side of l q lies. For vertical lines the left side of the line is interpeted as below.
>>>
Point2 10 10 `onSideUpDown` (lineThrough origin $ Point2 10 5)
Above>>>
Point2 10 10 `onSideUpDown` (lineThrough origin $ Point2 (-10) 5)
Above>>>
Point2 5 5 `onSideUpDown` (verticalLine 10)
Below>>>
Point2 5 5 `onSideUpDown` (lineThrough origin $ Point2 (-3) (-3))
On
Result of a side test
onSide :: (Ord r, Num r) => Point 2 r -> Line 2 r -> SideTest Source #
Given a point q and a line l, compute to which side of l q lies. For vertical lines the left side of the line is interpeted as below.
>>>
Point2 10 10 `onSide` (lineThrough origin $ Point2 10 5)
LeftSide>>>
Point2 10 10 `onSide` (lineThrough origin $ Point2 (-10) 5)
RightSide>>>
Point2 5 5 `onSide` (verticalLine 10)
LeftSide>>>
Point2 5 5 `onSide` (lineThrough origin $ Point2 (-3) (-3))
OnLine
liesAbove :: (Ord r, Num r) => Point 2 r -> Line 2 r -> Bool Source #
Test if the query point q lies (strictly) above line l
bisector :: Fractional r => Point 2 r -> Point 2 r -> Line 2 r Source #
Get the bisector between two points
cmpSlope :: (Num r, Ord r) => Line 2 r -> Line 2 r -> Ordering Source #
Compares the lines on slope. Vertical lines are considered larger than anything else.
>>>
(Line origin (Vector2 5 1)) `cmpSlope` (Line origin (Vector2 3 3))
LT>>>
(Line origin (Vector2 5 1)) `cmpSlope` (Line origin (Vector2 (-3) 3))
GT>>>
(Line origin (Vector2 5 1)) `cmpSlope` (Line origin (Vector2 0 1))
LT