hgeometry-0.6.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

Instances

Arity d => Functor (Line d) Source # 

Methods

fmap :: (a -> b) -> Line d a -> Line d b #

(<$) :: a -> Line d b -> Line d a #

Arity d => Foldable (Line d) Source # 

Methods

fold :: Monoid m => Line d m -> m #

foldMap :: Monoid m => (a -> m) -> Line d a -> m #

foldr :: (a -> b -> b) -> b -> Line d a -> b #

foldr' :: (a -> b -> b) -> b -> Line d a -> b #

foldl :: (b -> a -> b) -> b -> Line d a -> b #

foldl' :: (b -> a -> b) -> b -> Line d a -> b #

foldr1 :: (a -> a -> a) -> Line d a -> a #

foldl1 :: (a -> a -> a) -> Line d a -> a #

toList :: Line d a -> [a] #

null :: Line d a -> Bool #

length :: Line d a -> Int #

elem :: Eq a => a -> Line d a -> Bool #

maximum :: Ord a => Line d a -> a #

minimum :: Ord a => Line d a -> a #

sum :: Num a => Line d a -> a #

product :: Num a => Line d a -> a #

Arity d => Traversable (Line d) Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Line d a -> f (Line d b) #

sequenceA :: Applicative f => Line d (f a) -> f (Line d a) #

mapM :: Monad m => (a -> m b) -> Line d a -> m (Line d b) #

sequence :: Monad m => Line d (m a) -> m (Line d a) #

(Eq r, Arity d) => Eq (Line d r) Source # 

Methods

(==) :: Line d r -> Line d r -> Bool #

(/=) :: Line d r -> Line d r -> Bool #

(Show r, Arity d) => Show (Line d r) Source # 

Methods

showsPrec :: Int -> Line d r -> ShowS #

show :: Line d r -> String #

showList :: [Line d r] -> ShowS #

Generic (Line d r) Source # 

Associated Types

type Rep (Line d r) :: * -> * #

Methods

from :: Line d r -> Rep (Line d r) x #

to :: Rep (Line d r) x -> Line d r #

(NFData r, Arity d) => NFData (Line d r) Source # 

Methods

rnf :: Line d r -> () #

HasSupportingLine (Line d r) Source # 

Methods

supportingLine :: Line d r -> Line (Dimension (Line d r)) (NumType (Line d r)) Source #

(Eq r, Fractional r) => IsIntersectableWith (Line 2 r) (Line 2 r) Source # 

Methods

intersect :: Line 2 r -> Line 2 r -> Intersection (Line 2 r) (Line 2 r) Source #

intersects :: Line 2 r -> Line 2 r -> Bool Source #

nonEmptyIntersection :: proxy (Line 2 r) -> proxy (Line 2 r) -> Intersection (Line 2 r) (Line 2 r) -> Bool Source #

(Ord r, Floating r) => IsIntersectableWith (Line 2 r) (Circle p r) Source # 

Methods

intersect :: Line 2 r -> Circle p r -> Intersection (Line 2 r) (Circle p r) Source #

intersects :: Line 2 r -> Circle p r -> Bool Source #

nonEmptyIntersection :: proxy (Line 2 r) -> proxy (Circle p r) -> Intersection (Line 2 r) (Circle p r) -> Bool Source #

(Fractional r, Ord r, HasBoundingLines o) => IsIntersectableWith (Line 2 r) (Slab o a r) Source # 

Methods

intersect :: Line 2 r -> Slab o a r -> Intersection (Line 2 r) (Slab o a r) Source #

intersects :: Line 2 r -> Slab o a r -> Bool Source #

nonEmptyIntersection :: proxy (Line 2 r) -> proxy (Slab o a r) -> Intersection (Line 2 r) (Slab o a r) -> Bool Source #

(Ord r, Fractional r) => IsIntersectableWith (LineSegment 2 p r) (Line 2 r) Source # 

Methods

intersect :: LineSegment 2 p r -> Line 2 r -> Intersection (LineSegment 2 p r) (Line 2 r) Source #

intersects :: LineSegment 2 p r -> Line 2 r -> Bool Source #

nonEmptyIntersection :: proxy (LineSegment 2 p r) -> proxy (Line 2 r) -> Intersection (LineSegment 2 p r) (Line 2 r) -> Bool Source #

type Rep (Line d r) Source # 
type Rep (Line d r) = D1 (MetaData "Line" "Data.Geometry.Line.Internal" "hgeometry-0.6.0.0-ODn7ZyBfwj6IkLPAAzetJ" False) (C1 (MetaCons "Line" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_anchorPoint") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Point d r))) (S1 (MetaSel (Just Symbol "_direction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Vector d r)))))
type NumType (Line d r) Source # 
type NumType (Line d r) = r
type Dimension (Line d r) Source # 
type Dimension (Line d r) = d
type IntersectionOf (Line 2 r) (Boundary (Rectangle p r)) Source # 
type IntersectionOf (Line 2 r) (Boundary (Rectangle p r)) = (:) * NoIntersection ((:) * (Point 2 r) ((:) * (Point 2 r, Point 2 r) ((:) * (LineSegment 2 () r) ([] *))))
type IntersectionOf (Line 2 r) (Line 2 r) Source # 
type IntersectionOf (Line 2 r) (Line 2 r) = (:) * NoIntersection ((:) * (Point 2 r) ((:) * (Line 2 r) ([] *)))
type IntersectionOf (Line 2 r) (Rectangle p r) Source # 
type IntersectionOf (Line 2 r) (Rectangle p r) = (:) * NoIntersection ((:) * (Point 2 r) ((:) * (LineSegment 2 () r) ([] *)))
type IntersectionOf (Line 2 r) (Circle p r) Source # 
type IntersectionOf (Line 2 r) (Circle p r) = (:) * NoIntersection ((:) * (Touching (Point 2 r)) ((:) * (Point 2 r, Point 2 r) ([] *)))
type IntersectionOf (HalfLine 2 r) (Line 2 r) Source # 
type IntersectionOf (HalfLine 2 r) (Line 2 r) = (:) * NoIntersection ((:) * (Point 2 r) ((:) * (HalfLine 2 r) ([] *)))
type IntersectionOf (Line 2 r) (Slab o a r) Source # 
type IntersectionOf (Line 2 r) (Slab o a r) = (:) * NoIntersection ((:) * (Line 2 r) ((:) * (LineSegment 2 a r) ([] *)))
type IntersectionOf (LineSegment 2 p r) (Line 2 r) Source # 
type IntersectionOf (LineSegment 2 p r) (Line 2 r) = (:) * NoIntersection ((:) * (Point 2 r) ((:) * (LineSegment 2 p r) ([] *)))

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.

Minimal complete definition

supportingLine

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

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