hgeometry-0.5.0.0: Geometric Algorithms, Data structures, and Data types.

Safe HaskellNone
LanguageHaskell2010

Data.Geometry.Line.Internal

Contents

Synopsis

d-dimensional Lines

data Line d r Source

A line is given by an anchor point and a vector indicating the direction.

Constructors

Line 

Fields

_anchorPoint :: Point d r
 
_direction :: Vector d r
 

Instances

Arity d => Functor (Line d) Source 
Arity d => Foldable (Line d) Source 
Arity d => Traversable (Line d) Source 
(Eq r, Arity d) => Eq (Line d r) Source 
(Show r, Arity d) => Show (Line d r) Source 
HasSupportingLine (Line d r) Source 
(Eq r, Fractional r) => IsIntersectableWith (Line 2 r) (Line 2 r) Source 
(Ord r, Floating r) => IsIntersectableWith (Line 2 r) (Circle p r) Source 
(Fractional r, Ord r, HasBoundingLines o) => IsIntersectableWith (Line 2 r) (Slab o a r) Source 
(Ord r, Fractional r) => IsIntersectableWith (LineSegment 2 p r) (Line 2 r) Source 
type NumType (Line d r) = r Source 
type Dimension (Line d r) = d Source 
type IntersectionOf (Line 2 r) (Boundary (Rectangle p r)) = (:) * NoIntersection ((:) * (Point 2 r) ((:) * (Point 2 r, Point 2 r) ((:) * (LineSegment 2 () r) ([] *)))) Source 
type IntersectionOf (Line 2 r) (Line 2 r) = (:) * NoIntersection ((:) * (Point 2 r) ((:) * (Line 2 r) ([] *))) Source

The intersection of two lines is either: NoIntersection, a point or a line.

type IntersectionOf (Line 2 r) (Rectangle p r) = (:) * NoIntersection ((:) * (Point 2 r) ((:) * (LineSegment 2 () r) ([] *))) Source 
type IntersectionOf (Line 2 r) (Circle p r) = (:) * NoIntersection ((:) * (Touching (Point 2 r)) ((:) * (Point 2 r, Point 2 r) ([] *))) Source

No intersection, one touching point, or two points

type IntersectionOf (HalfLine 2 r) (Line 2 r) = (:) * NoIntersection ((:) * (Point 2 r) ((:) * (HalfLine 2 r) ([] *))) Source 
type IntersectionOf (Line 2 r) (Slab o a r) = (:) * NoIntersection ((:) * (Line 2 r) ((:) * (LineSegment 2 a r) ([] *))) Source 
type IntersectionOf (LineSegment 2 p r) (Line 2 r) = (:) * NoIntersection ((:) * (Point 2 r) ((:) * (LineSegment 2 p r) ([] *))) Source 

direction :: forall d r. Lens' (Line d r) (Vector d r) Source

anchorPoint :: forall d r. Lens' (Line d r) (Point d r) Source

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, get the line perpendicular to l that also goes through p.

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

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.

Methods

supportingLine :: t -> Line (Dimension t) (NumType t) 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 SideTest Source

Result of a side test

Constructors

Below 
On 
Above 

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)
Above
>>> point2 10 10 `onSide` (lineThrough origin $ point2 (-10) 5)
Above
>>> point2 5 5 `onSide` (verticalLine 10)
Below
>>> point2 5 5 `onSide` (lineThrough origin $ point2 (-3) (-3))
On

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