hgeometry-1.0.0.0: Geometric Algorithms, Data structures, and Data types.
Copyright(C) Frank Staals
Licensesee the LICENSE file
MaintainerFrank Staals
Safe HaskellSafe-Inferred
LanguageGHC2021

HGeometry.LineSegment

Description

Line segment data type and some basic functions on line segments

Synopsis

Documentation

data LineSegment endPoint point where Source #

Data type representing intervals

Bundled Patterns

pattern LineSegment :: endPoint point -> endPoint point -> LineSegment endPoint point

Construct a line Segment

pattern ClosedLineSegment :: point -> point -> ClosedLineSegment point

Construct a closed interval

pattern OpenLineSegment :: point -> point -> OpenLineSegment point

Construct an open ended interval

Instances

Instances details
Foldable endPoint => Foldable (LineSegment endPoint) Source # 
Instance details

Defined in HGeometry.LineSegment.Internal

Methods

fold :: Monoid m => LineSegment endPoint m -> m #

foldMap :: Monoid m => (a -> m) -> LineSegment endPoint a -> m #

foldMap' :: Monoid m => (a -> m) -> LineSegment endPoint a -> m #

foldr :: (a -> b -> b) -> b -> LineSegment endPoint a -> b #

foldr' :: (a -> b -> b) -> b -> LineSegment endPoint a -> b #

foldl :: (b -> a -> b) -> b -> LineSegment endPoint a -> b #

foldl' :: (b -> a -> b) -> b -> LineSegment endPoint a -> b #

foldr1 :: (a -> a -> a) -> LineSegment endPoint a -> a #

foldl1 :: (a -> a -> a) -> LineSegment endPoint a -> a #

toList :: LineSegment endPoint a -> [a] #

null :: LineSegment endPoint a -> Bool #

length :: LineSegment endPoint a -> Int #

elem :: Eq a => a -> LineSegment endPoint a -> Bool #

maximum :: Ord a => LineSegment endPoint a -> a #

minimum :: Ord a => LineSegment endPoint a -> a #

sum :: Num a => LineSegment endPoint a -> a #

product :: Num a => LineSegment endPoint a -> a #

Traversable endPoint => Traversable (LineSegment endPoint) Source # 
Instance details

Defined in HGeometry.LineSegment.Internal

Methods

traverse :: Applicative f => (a -> f b) -> LineSegment endPoint a -> f (LineSegment endPoint b) #

sequenceA :: Applicative f => LineSegment endPoint (f a) -> f (LineSegment endPoint a) #

mapM :: Monad m => (a -> m b) -> LineSegment endPoint a -> m (LineSegment endPoint b) #

sequence :: Monad m => LineSegment endPoint (m a) -> m (LineSegment endPoint a) #

Functor endPoint => Functor (LineSegment endPoint) Source # 
Instance details

Defined in HGeometry.LineSegment.Internal

Methods

fmap :: (a -> b) -> LineSegment endPoint a -> LineSegment endPoint b #

(<$) :: a -> LineSegment endPoint b -> LineSegment endPoint a #

Read point => Read (ClosedLineSegment point) Source # 
Instance details

Defined in HGeometry.LineSegment.Internal

Show point => Show (ClosedLineSegment point) Source # 
Instance details

Defined in HGeometry.LineSegment.Internal

(Fractional r, Ord r, HasSquaredEuclideanDistance point, Point_ point d r) => HasSquaredEuclideanDistance (ClosedLineSegment point) Source # 
Instance details

Defined in HGeometry.LineSegment.Internal

Methods

squaredEuclideanDistTo :: forall r (d :: Nat) point0. (r ~ NumType (ClosedLineSegment point), d ~ Dimension (ClosedLineSegment point), Num r, Point_ point0 d r) => point0 -> ClosedLineSegment point -> r Source #

pointClosestTo :: forall r (d :: Nat) point0. (r ~ NumType (ClosedLineSegment point), d ~ Dimension (ClosedLineSegment point), Num r, Point_ point0 d r) => point0 -> ClosedLineSegment point -> Point d r Source #

pointClosestToWithDistance :: forall r (d :: Nat) point0. (r ~ NumType (ClosedLineSegment point), d ~ Dimension (ClosedLineSegment point), Num r, Point_ point0 d r) => point0 -> ClosedLineSegment point -> (Point d r, r) Source #

Point_ point (Dimension point) (NumType point) => ClosedLineSegment_ (ClosedLineSegment point) point Source # 
Instance details

Defined in HGeometry.LineSegment.Internal

(Point_ point d r, Fractional r) => HasOnSegment (ClosedLineSegment point) d Source # 
Instance details

Defined in HGeometry.LineSegment.Internal

Methods

onSegment :: (Ord r, Point_ point0 d r, r ~ NumType (ClosedLineSegment point), d ~ Dimension (ClosedLineSegment point)) => point0 -> ClosedLineSegment point -> Bool Source #

(Point_ point 2 r, Num r) => HasOnSegment (ClosedLineSegment point) 2 Source # 
Instance details

Defined in HGeometry.LineSegment.Internal

Methods

onSegment :: (Ord r, Point_ point0 2 r, r ~ NumType (ClosedLineSegment point), 2 ~ Dimension (ClosedLineSegment point)) => point0 -> ClosedLineSegment point -> Bool Source #

(Point_ point d r, Fractional r) => HasOnSegment (OpenLineSegment point) d Source # 
Instance details

Defined in HGeometry.LineSegment.Internal

Methods

onSegment :: (Ord r, Point_ point0 d r, r ~ NumType (OpenLineSegment point), d ~ Dimension (OpenLineSegment point)) => point0 -> OpenLineSegment point -> Bool Source #

(Point_ point 2 r, Num r) => HasOnSegment (OpenLineSegment point) 2 Source # 
Instance details

Defined in HGeometry.LineSegment.Internal

Methods

onSegment :: (Ord r, Point_ point0 2 r, r ~ NumType (OpenLineSegment point), 2 ~ Dimension (OpenLineSegment point)) => point0 -> OpenLineSegment point -> Bool Source #

Point_ point (Dimension point) (NumType point) => OpenLineSegment_ (OpenLineSegment point) point Source # 
Instance details

Defined in HGeometry.LineSegment.Internal

(Point_ point 2 r, Num r, Ord r) => HasIntersectionWith (ClosedLineSegment point) (OpenLineSegment point) Source # 
Instance details

Defined in HGeometry.LineSegment.Intersection

(Point_ point d r, Point_ point' d r, Ord r, Fractional r, Has_ Metric_ d r, HasSquaredEuclideanDistance point') => HasIntersectionWith (ClosedLineSegment point') (Ball point) Source # 
Instance details

Defined in HGeometry.Ball.CenterAndRadius

Methods

intersects :: ClosedLineSegment point' -> Ball point -> Bool Source #

(Point_ point d r, Point_ point' d r, Ord r, Fractional r, Has_ Metric_ d r, HasSquaredEuclideanDistance point') => HasIntersectionWith (ClosedLineSegment point') (Sphere point) Source # 
Instance details

Defined in HGeometry.Ball.CenterAndRadius

Methods

intersects :: ClosedLineSegment point' -> Sphere point -> Bool Source #

(Point_ point 2 r, Num r, Ord r) => HasIntersectionWith (OpenLineSegment point) (ClosedLineSegment point) Source # 
Instance details

Defined in HGeometry.LineSegment.Intersection

(Point_ point 2 r, Fractional r, Ord r) => IsIntersectableWith (LineEQ r) (ClosedLineSegment point) Source # 
Instance details

Defined in HGeometry.LineSegment.Intersection

(Point_ point 2 r, Fractional r, Ord r) => IsIntersectableWith (LineEQ r) (OpenLineSegment point) Source # 
Instance details

Defined in HGeometry.LineSegment.Intersection

(Ord r, Num r, Point_ point 2 r, IxValue (endPoint point) ~ point, EndPoint_ (endPoint point)) => HasIntersectionWith (HalfLine point) (LineSegment endPoint point) Source # 
Instance details

Defined in HGeometry.LineSegment.Intersection

Methods

intersects :: HalfLine point -> LineSegment endPoint point -> Bool Source #

(Point_ point 2 r, Num r, Ord r, IxValue (endPoint point) ~ point, EndPoint_ (endPoint point)) => HasIntersectionWith (LineEQ r) (LineSegment endPoint point) Source # 
Instance details

Defined in HGeometry.LineSegment.Intersection

Methods

intersects :: LineEQ r -> LineSegment endPoint point -> Bool Source #

(Point_ point 2 r, Num r, Ord r) => HasIntersectionWith (ClosedLineSegment point) (LineSegment AnEndPoint point) Source # 
Instance details

Defined in HGeometry.LineSegment.Intersection

(Point_ point 2 r, Num r, Ord r) => HasIntersectionWith (OpenLineSegment point) (LineSegment AnEndPoint point) Source # 
Instance details

Defined in HGeometry.LineSegment.Intersection

(Ord r, Fractional r, Point_ point 2 r, IxValue (endPoint point) ~ point, EndPoint_ (endPoint point), IsIntersectableWith (LinePV 2 r) (LineSegment endPoint point), Intersection (LinePV 2 r) (LineSegment endPoint point) ~ Maybe (LineLineSegmentIntersection lineSegment'), NumType lineSegment' ~ r) => IsIntersectableWith (HalfLine point) (LineSegment endPoint point) Source # 
Instance details

Defined in HGeometry.LineSegment.Intersection

Methods

intersect :: HalfLine point -> LineSegment endPoint point -> Intersection (HalfLine point) (LineSegment endPoint point) Source #

(Point_ point 2 r, Fractional r, Ord r) => IsIntersectableWith (LineEQ r) (LineSegment AnEndPoint point) Source # 
Instance details

Defined in HGeometry.LineSegment.Intersection

Read (endPoint point) => Read (LineSegment endPoint point) Source # 
Instance details

Defined in HGeometry.LineSegment.Internal

Methods

readsPrec :: Int -> ReadS (LineSegment endPoint point) #

readList :: ReadS [LineSegment endPoint point] #

readPrec :: ReadPrec (LineSegment endPoint point) #

readListPrec :: ReadPrec [LineSegment endPoint point] #

(Show point, Show (ClosedLineSegment point)) => Show (IntersectionOf (ClosedLineSegment point) (Ball point)) Source # 
Instance details

Defined in HGeometry.Ball.CenterAndRadius

Show (endPoint point) => Show (LineSegment endPoint point) Source # 
Instance details

Defined in HGeometry.LineSegment.Internal

Methods

showsPrec :: Int -> LineSegment endPoint point -> ShowS #

show :: LineSegment endPoint point -> String #

showList :: [LineSegment endPoint point] -> ShowS #

(Eq point, Eq (ClosedLineSegment point)) => Eq (IntersectionOf (ClosedLineSegment point) (Ball point)) Source # 
Instance details

Defined in HGeometry.Ball.CenterAndRadius

Eq (endPoint point) => Eq (LineSegment endPoint point) Source # 
Instance details

Defined in HGeometry.LineSegment.Internal

Methods

(==) :: LineSegment endPoint point -> LineSegment endPoint point -> Bool #

(/=) :: LineSegment endPoint point -> LineSegment endPoint point -> Bool #

Ord (endPoint point) => Ord (LineSegment endPoint point) Source # 
Instance details

Defined in HGeometry.LineSegment.Internal

Methods

compare :: LineSegment endPoint point -> LineSegment endPoint point -> Ordering #

(<) :: LineSegment endPoint point -> LineSegment endPoint point -> Bool #

(<=) :: LineSegment endPoint point -> LineSegment endPoint point -> Bool #

(>) :: LineSegment endPoint point -> LineSegment endPoint point -> Bool #

(>=) :: LineSegment endPoint point -> LineSegment endPoint point -> Bool #

max :: LineSegment endPoint point -> LineSegment endPoint point -> LineSegment endPoint point #

min :: LineSegment endPoint point -> LineSegment endPoint point -> LineSegment endPoint point #

(Traversable1 endPoint, Point_ point d r, d ~ Dimension point, r ~ NumType point, Ord r, Ord (Vector d r)) => IsBoxable (LineSegment endPoint point) Source # 
Instance details

Defined in HGeometry.LineSegment.Internal

Methods

boundingBox :: forall (d :: Nat) r. (d ~ Dimension (LineSegment endPoint point), r ~ NumType (LineSegment endPoint point), Ord r) => LineSegment endPoint point -> Box (Point d r) Source #

(Point_ point d r, Has_ Metric_ d r, EndPoint_ (endPoint point), IxValue (endPoint point) ~ point, Num r) => HasSupportingLine (LineSegment endPoint point) Source # 
Instance details

Defined in HGeometry.LineSegment.Internal

Methods

supportingLine :: LineSegment endPoint point -> LinePV (Dimension (LineSegment endPoint point)) (NumType (LineSegment endPoint point)) Source #

(Point_ point d r, IxValue (endPoint point) ~ point, EndPoint_ (endPoint point), IsTransformable point) => IsTransformable (LineSegment endPoint point) Source # 
Instance details

Defined in HGeometry.LineSegment.Internal

Methods

transformBy :: Transformation (Dimension (LineSegment endPoint point)) (NumType (LineSegment endPoint point)) -> LineSegment endPoint point -> LineSegment endPoint point Source #

(IxValue (endPoint point) ~ point, EndPoint_ (endPoint point)) => HasEnd (LineSegment endPoint point) point Source # 
Instance details

Defined in HGeometry.LineSegment.Internal

Methods

end :: Lens' (LineSegment endPoint point) point Source #

(IxValue (endPoint point) ~ point, EndPoint_ (endPoint point)) => HasStart (LineSegment endPoint point) point Source # 
Instance details

Defined in HGeometry.LineSegment.Internal

Methods

start :: Lens' (LineSegment endPoint point) point Source #

(IxValue (endPoint point) ~ point, EndPoint_ (endPoint point)) => IntervalLike_ (LineSegment endPoint point) point Source # 
Instance details

Defined in HGeometry.LineSegment.Internal

(IxValue (endPoint point) ~ point, EndPoint_ (endPoint point), Point_ point (Dimension point) (NumType point)) => ConstructableLineSegment_ (LineSegment endPoint point) point Source # 
Instance details

Defined in HGeometry.LineSegment.Internal

Methods

uncheckedLineSegment :: point -> point -> LineSegment endPoint point Source #

mkLineSegment :: point -> point -> Maybe (LineSegment endPoint point) Source #

(Point_ point d r, Fractional r) => HasOnSegment (LineSegment AnEndPoint point) d Source # 
Instance details

Defined in HGeometry.LineSegment.Internal

Methods

onSegment :: (Ord r, Point_ point0 d r, r ~ NumType (LineSegment AnEndPoint point), d ~ Dimension (LineSegment AnEndPoint point)) => point0 -> LineSegment AnEndPoint point -> Bool Source #

(Point_ point 2 r, Num r) => HasOnSegment (LineSegment AnEndPoint point) 2 Source # 
Instance details

Defined in HGeometry.LineSegment.Internal

Methods

onSegment :: (Ord r, Point_ point0 2 r, r ~ NumType (LineSegment AnEndPoint point), 2 ~ Dimension (LineSegment AnEndPoint point)) => point0 -> LineSegment AnEndPoint point -> Bool Source #

(IxValue (endPoint point) ~ point, EndPoint_ (endPoint point), Point_ point (Dimension point) (NumType point)) => LineSegment_ (LineSegment endPoint point) point Source # 
Instance details

Defined in HGeometry.LineSegment.Internal

(Point_ point 2 r, Num r, Ord r) => HasIntersectionWith (LineSegment AnEndPoint point) (ClosedLineSegment point) Source # 
Instance details

Defined in HGeometry.LineSegment.Intersection

(Point_ point 2 r, Num r, Ord r) => HasIntersectionWith (LineSegment AnEndPoint point) (OpenLineSegment point) Source # 
Instance details

Defined in HGeometry.LineSegment.Intersection

(Ord r, Num r, Point_ point 2 r, Point_ point' 2 r, HasIntersectionWith (LineSegment endPoint point) (ClosedLineSegment point')) => HasIntersectionWith (LineSegment endPoint point) (Boundary (Rectangle point')) Source # 
Instance details

Defined in HGeometry.Box

Methods

intersects :: LineSegment endPoint point -> Boundary (Rectangle point') -> Bool Source #

(Ord r, Num r, Point_ point 2 r, Point_ point' 2 r, IxValue (endPoint point) ~ point, EndPoint_ (endPoint point), HasIntersectionWith (LineSegment endPoint point) (ClosedLineSegment point')) => HasIntersectionWith (LineSegment endPoint point) (Rectangle point') Source # 
Instance details

Defined in HGeometry.Box

Methods

intersects :: LineSegment endPoint point -> Rectangle point' -> Bool Source #

(Point_ point 2 r, Fractional r, Ord r) => IsIntersectableWith (LinePV 2 r) (ClosedLineSegment point) Source # 
Instance details

Defined in HGeometry.LineSegment.Intersection

(Point_ point 2 r, Fractional r, Ord r) => IsIntersectableWith (LinePV 2 r) (OpenLineSegment point) Source # 
Instance details

Defined in HGeometry.LineSegment.Intersection

Methods

intersect :: LinePV 2 r -> OpenLineSegment point -> Intersection (LinePV 2 r) (OpenLineSegment point) Source #

IxValue (endPoint point) ~ point => HasEndPoint (LineSegment endPoint point) (endPoint point) Source # 
Instance details

Defined in HGeometry.LineSegment.Internal

Methods

endPoint :: Lens' (LineSegment endPoint point) (endPoint point) Source #

IxValue (endPoint point) ~ point => HasStartPoint (LineSegment endPoint point) (endPoint point) Source # 
Instance details

Defined in HGeometry.LineSegment.Internal

Methods

startPoint :: Lens' (LineSegment endPoint point) (endPoint point) Source #

(Point_ point 2 r, Num r, Ord r, IxValue (endPoint point) ~ point, EndPoint_ (endPoint point)) => HasIntersectionWith (LinePV 2 r) (LineSegment endPoint point) Source # 
Instance details

Defined in HGeometry.LineSegment.Intersection

Methods

intersects :: LinePV 2 r -> LineSegment endPoint point -> Bool Source #

(Point_ point 2 r, Num r, Ord r, Functor endPoint, IxValue (endPoint point) ~ point, EndPoint_ (endPoint point), IxValue (endPoint r) ~ r, EndPoint_ (endPoint r), HasIntersectionWith (Interval endPoint r) (Interval endPoint r)) => HasIntersectionWith (LineSegment endPoint point) (LineSegment endPoint point) Source # 
Instance details

Defined in HGeometry.LineSegment.Intersection

Methods

intersects :: LineSegment endPoint point -> LineSegment endPoint point -> Bool Source #

(HasOnSegment (LineSegment endPoint point) d, Point_ point d r, Fractional r, Ord r) => HasIntersectionWith (Point d r) (LineSegment endPoint point) Source # 
Instance details

Defined in HGeometry.LineSegment.Internal

Methods

intersects :: Point d r -> LineSegment endPoint point -> Bool Source #

(HasOnSegment (LineSegment endPoint point) 2, Point_ point 2 r, Num r, Ord r, IxValue (endPoint point) ~ point, EndPoint_ (endPoint point)) => HasIntersectionWith (Point 2 r) (LineSegment endPoint point) Source # 
Instance details

Defined in HGeometry.LineSegment.Internal

Methods

intersects :: Point 2 r -> LineSegment endPoint point -> Bool Source #

(Point_ point 2 r, Fractional r, Ord r) => IsIntersectableWith (LinePV 2 r) (LineSegment AnEndPoint point) Source # 
Instance details

Defined in HGeometry.LineSegment.Intersection

(Point_ point 2 r, Num r, Ord r, Functor endPoint, IxValue (endPoint point) ~ point, EndPoint_ (endPoint point), IxValue (endPoint r) ~ r, EndPoint_ (endPoint r), HasIntersectionWith (Interval endPoint r) (Interval endPoint r), IxValue (endPoint point) ~ point, IxValue (endPoint (r :+ endPoint point)) ~ (r :+ endPoint point), EndPoint_ (endPoint point), IsEndPoint (endPoint point) (endPoint (r :+ endPoint point)), IsIntersectableWith (LinePV 2 r) (LineSegment endPoint point), Intersection (LinePV 2 r) (LineSegment endPoint point) ~ Maybe (LineLineSegmentIntersection (LineSegment endPoint point)), HasOnSegment (LineSegment endPoint point) 2, IsIntersectableWith (Interval endPoint (r :+ endPoint point)) (Interval endPoint (r :+ endPoint point)), Intersection (LineSegment endPoint point) (LineSegment endPoint point) ~ Maybe (LineSegmentLineSegmentIntersection (LineSegment endPoint point)), EndPoint_ (endPoint (r :+ endPoint point))) => IsIntersectableWith (LineSegment endPoint point) (LineSegment endPoint point) Source # 
Instance details

Defined in HGeometry.LineSegment.Intersection

Methods

intersect :: LineSegment endPoint point -> LineSegment endPoint point -> Intersection (LineSegment endPoint point) (LineSegment endPoint point) Source #

(IsIntersectableWith (LineSegment endPoint point) (LineSegment endPoint point), Intersection (LineSegment endPoint point) (LineSegment endPoint point) ~ Maybe (LineSegmentLineSegmentIntersection (LineSegment endPoint point))) => IsIntersectableWith (LineSegment endPoint point :+ extra) (LineSegment endPoint point :+ extra) Source # 
Instance details

Defined in HGeometry.LineSegment.Intersection

Methods

intersect :: (LineSegment endPoint point :+ extra) -> (LineSegment endPoint point :+ extra) -> Intersection (LineSegment endPoint point :+ extra) (LineSegment endPoint point :+ extra) Source #

(Traversable1 endPoint, Dimension point ~ Dimension point', Point_ point (Dimension point) (NumType point), Point_ point' (Dimension point) (NumType point')) => HasPoints (LineSegment endPoint point) (LineSegment endPoint point') point point' Source # 
Instance details

Defined in HGeometry.LineSegment.Internal

Methods

allPoints :: forall (d :: Nat) r r'. (Point_ point d r, Point_ point' d r', NumType (LineSegment endPoint point) ~ r, NumType (LineSegment endPoint point') ~ r', Dimension (LineSegment endPoint point) ~ d, Dimension (LineSegment endPoint point') ~ d) => Traversal1 (LineSegment endPoint point) (LineSegment endPoint point') point point' Source #

type Intersection (ClosedLineSegment point) (Ball point) Source # 
Instance details

Defined in HGeometry.Ball.CenterAndRadius

data IntersectionOf (ClosedLineSegment point) (Ball point) Source # 
Instance details

Defined in HGeometry.Ball.CenterAndRadius

type Intersection (HalfLine point) (LineSegment endPoint point) Source # 
Instance details

Defined in HGeometry.LineSegment.Intersection

type Intersection (HalfLine point) (LineSegment endPoint point) = Maybe (HalfLineLineSegmentIntersection (Point 2 (NumType point)) (LineSegment endPoint point))
type Intersection (LineEQ r) (LineSegment AnEndPoint point) Source # 
Instance details

Defined in HGeometry.LineSegment.Intersection

type Intersection (LineEQ r) (LineSegment (EndPoint t) point) Source # 
Instance details

Defined in HGeometry.LineSegment.Intersection

type EndPointOf (LineSegment endPoint point) Source # 
Instance details

Defined in HGeometry.LineSegment.Internal

type EndPointOf (LineSegment endPoint point) = endPoint point
type StartPointOf (LineSegment endPoint point) Source # 
Instance details

Defined in HGeometry.LineSegment.Internal

type StartPointOf (LineSegment endPoint point) = endPoint point
type Dimension (LineSegment endPoint point) Source # 
Instance details

Defined in HGeometry.LineSegment.Internal

type Dimension (LineSegment endPoint point) = Dimension point
type NumType (LineSegment endPoint point) Source # 
Instance details

Defined in HGeometry.LineSegment.Internal

type NumType (LineSegment endPoint point) = NumType point
type Intersection (LinePV 2 r) (LineSegment AnEndPoint point) Source # 
Instance details

Defined in HGeometry.LineSegment.Intersection

type Intersection (LinePV 2 r) (LineSegment (EndPoint t) point) Source # 
Instance details

Defined in HGeometry.LineSegment.Intersection

type Intersection (LinePV 2 r) (LineSegment (EndPoint t) point)
type Intersection (LineSegment AnEndPoint point) (LineSegment AnEndPoint point) Source # 
Instance details

Defined in HGeometry.LineSegment.Intersection

type Intersection (LineSegment (EndPoint t) point) (LineSegment (EndPoint t) point) Source # 
Instance details

Defined in HGeometry.LineSegment.Intersection

type Intersection (LineSegment endPoint point :+ extra) (LineSegment endPoint point :+ extra) Source # 
Instance details

Defined in HGeometry.LineSegment.Intersection

type Intersection (LineSegment endPoint point :+ extra) (LineSegment endPoint point :+ extra) = Maybe (LineSegmentLineSegmentIntersection (LineSegment endPoint point :+ extra))

type ClosedLineSegment point = LineSegment (EndPoint Closed) point Source #

A type representing Closed LineSegments

type OpenLineSegment point = LineSegment (EndPoint Open) point Source #

A type representing Open LineSegments

newtype EndPoint (et :: EndPointType) r Source #

EndPoint with a type safe tag

Constructors

EndPoint r 

Bundled Patterns

pattern OpenE :: r -> EndPoint Open r

Constructs an Open endpoint

pattern ClosedE :: r -> EndPoint Closed r

Constructs a closed endpoint

Instances

Instances details
Foldable (EndPoint et) Source # 
Instance details

Defined in HGeometry.Interval.EndPoint

Methods

fold :: Monoid m => EndPoint et m -> m #

foldMap :: Monoid m => (a -> m) -> EndPoint et a -> m #

foldMap' :: Monoid m => (a -> m) -> EndPoint et a -> m #

foldr :: (a -> b -> b) -> b -> EndPoint et a -> b #

foldr' :: (a -> b -> b) -> b -> EndPoint et a -> b #

foldl :: (b -> a -> b) -> b -> EndPoint et a -> b #

foldl' :: (b -> a -> b) -> b -> EndPoint et a -> b #

foldr1 :: (a -> a -> a) -> EndPoint et a -> a #

foldl1 :: (a -> a -> a) -> EndPoint et a -> a #

toList :: EndPoint et a -> [a] #

null :: EndPoint et a -> Bool #

length :: EndPoint et a -> Int #

elem :: Eq a => a -> EndPoint et a -> Bool #

maximum :: Ord a => EndPoint et a -> a #

minimum :: Ord a => EndPoint et a -> a #

sum :: Num a => EndPoint et a -> a #

product :: Num a => EndPoint et a -> a #

Foldable1 (EndPoint et) Source # 
Instance details

Defined in HGeometry.Interval.EndPoint

Methods

fold1 :: Semigroup m => EndPoint et m -> m #

foldMap1 :: Semigroup m => (a -> m) -> EndPoint et a -> m #

foldMap1' :: Semigroup m => (a -> m) -> EndPoint et a -> m #

toNonEmpty :: EndPoint et a -> NonEmpty a #

maximum :: Ord a => EndPoint et a -> a #

minimum :: Ord a => EndPoint et a -> a #

head :: EndPoint et a -> a #

last :: EndPoint et a -> a #

foldrMap1 :: (a -> b) -> (a -> b -> b) -> EndPoint et a -> b #

foldlMap1' :: (a -> b) -> (b -> a -> b) -> EndPoint et a -> b #

foldlMap1 :: (a -> b) -> (b -> a -> b) -> EndPoint et a -> b #

foldrMap1' :: (a -> b) -> (a -> b -> b) -> EndPoint et a -> b #

Traversable (EndPoint et) Source # 
Instance details

Defined in HGeometry.Interval.EndPoint

Methods

traverse :: Applicative f => (a -> f b) -> EndPoint et a -> f (EndPoint et b) #

sequenceA :: Applicative f => EndPoint et (f a) -> f (EndPoint et a) #

mapM :: Monad m => (a -> m b) -> EndPoint et a -> m (EndPoint et b) #

sequence :: Monad m => EndPoint et (m a) -> m (EndPoint et a) #

Functor (EndPoint et) Source # 
Instance details

Defined in HGeometry.Interval.EndPoint

Methods

fmap :: (a -> b) -> EndPoint et a -> EndPoint et b #

(<$) :: a -> EndPoint et b -> EndPoint et a #

Read point => Read (ClosedLineSegment point) Source # 
Instance details

Defined in HGeometry.LineSegment.Internal

Show point => Show (ClosedLineSegment point) Source # 
Instance details

Defined in HGeometry.LineSegment.Internal

(Fractional r, Ord r, HasSquaredEuclideanDistance point, Point_ point d r) => HasSquaredEuclideanDistance (ClosedLineSegment point) Source # 
Instance details

Defined in HGeometry.LineSegment.Internal

Methods

squaredEuclideanDistTo :: forall r (d :: Nat) point0. (r ~ NumType (ClosedLineSegment point), d ~ Dimension (ClosedLineSegment point), Num r, Point_ point0 d r) => point0 -> ClosedLineSegment point -> r Source #

pointClosestTo :: forall r (d :: Nat) point0. (r ~ NumType (ClosedLineSegment point), d ~ Dimension (ClosedLineSegment point), Num r, Point_ point0 d r) => point0 -> ClosedLineSegment point -> Point d r Source #

pointClosestToWithDistance :: forall r (d :: Nat) point0. (r ~ NumType (ClosedLineSegment point), d ~ Dimension (ClosedLineSegment point), Num r, Point_ point0 d r) => point0 -> ClosedLineSegment point -> (Point d r, r) Source #

Traversable1 (EndPoint et) Source # 
Instance details

Defined in HGeometry.Interval.EndPoint

Methods

traverse1 :: Apply f => (a -> f b) -> EndPoint et a -> f (EndPoint et b) Source #

sequence1 :: Apply f => EndPoint et (f b) -> f (EndPoint et b) Source #

ClosedInterval_ (ClosedInterval r) r Source # 
Instance details

Defined in HGeometry.Interval.Internal

ConstructableClosedInterval_ (ClosedInterval r) r Source # 
Instance details

Defined in HGeometry.Interval.Internal

ConstructableOpenInterval_ (OpenInterval r) r Source # 
Instance details

Defined in HGeometry.Interval.Internal

Methods

mkOpenInterval :: r -> r -> OpenInterval r Source #

OpenInterval_ (OpenInterval r) r Source # 
Instance details

Defined in HGeometry.Interval.Internal

Point_ point (Dimension point) (NumType point) => ClosedLineSegment_ (ClosedLineSegment point) point Source # 
Instance details

Defined in HGeometry.LineSegment.Internal

(Point_ point d r, Fractional r) => HasOnSegment (ClosedLineSegment point) d Source # 
Instance details

Defined in HGeometry.LineSegment.Internal

Methods

onSegment :: (Ord r, Point_ point0 d r, r ~ NumType (ClosedLineSegment point), d ~ Dimension (ClosedLineSegment point)) => point0 -> ClosedLineSegment point -> Bool Source #

(Point_ point 2 r, Num r) => HasOnSegment (ClosedLineSegment point) 2 Source # 
Instance details

Defined in HGeometry.LineSegment.Internal

Methods

onSegment :: (Ord r, Point_ point0 2 r, r ~ NumType (ClosedLineSegment point), 2 ~ Dimension (ClosedLineSegment point)) => point0 -> ClosedLineSegment point -> Bool Source #

(Point_ point d r, Fractional r) => HasOnSegment (OpenLineSegment point) d Source # 
Instance details

Defined in HGeometry.LineSegment.Internal

Methods

onSegment :: (Ord r, Point_ point0 d r, r ~ NumType (OpenLineSegment point), d ~ Dimension (OpenLineSegment point)) => point0 -> OpenLineSegment point -> Bool Source #

(Point_ point 2 r, Num r) => HasOnSegment (OpenLineSegment point) 2 Source # 
Instance details

Defined in HGeometry.LineSegment.Internal

Methods

onSegment :: (Ord r, Point_ point0 2 r, r ~ NumType (OpenLineSegment point), 2 ~ Dimension (OpenLineSegment point)) => point0 -> OpenLineSegment point -> Bool Source #

Point_ point (Dimension point) (NumType point) => OpenLineSegment_ (OpenLineSegment point) point Source # 
Instance details

Defined in HGeometry.LineSegment.Internal

Ord r => HasIntersectionWith (ClosedInterval r) (HalfOpenInterval r) Source # 
Instance details

Defined in HGeometry.Interval.HalfOpen

Ord r => HasIntersectionWith (OpenInterval r) (ClosedInterval r) Source # 
Instance details

Defined in HGeometry.Interval.Internal

Ord r => HasIntersectionWith (OpenInterval r) (OpenInterval r) Source # 
Instance details

Defined in HGeometry.Interval.Internal

(Point_ point 2 r, Num r, Ord r) => HasIntersectionWith (ClosedLineSegment point) (OpenLineSegment point) Source # 
Instance details

Defined in HGeometry.LineSegment.Intersection

(Point_ point d r, Point_ point' d r, Ord r, Fractional r, Has_ Metric_ d r, HasSquaredEuclideanDistance point') => HasIntersectionWith (ClosedLineSegment point') (Ball point) Source # 
Instance details

Defined in HGeometry.Ball.CenterAndRadius

Methods

intersects :: ClosedLineSegment point' -> Ball point -> Bool Source #

(Point_ point d r, Point_ point' d r, Ord r, Fractional r, Has_ Metric_ d r, HasSquaredEuclideanDistance point') => HasIntersectionWith (ClosedLineSegment point') (Sphere point) Source # 
Instance details

Defined in HGeometry.Ball.CenterAndRadius

Methods

intersects :: ClosedLineSegment point' -> Sphere point -> Bool Source #

(Point_ point 2 r, Num r, Ord r) => HasIntersectionWith (OpenLineSegment point) (ClosedLineSegment point) Source # 
Instance details

Defined in HGeometry.LineSegment.Intersection

Ord r => IsIntersectableWith (ClosedInterval r) (ClosedInterval r) Source # 
Instance details

Defined in HGeometry.Interval.Internal

Ord r => IsIntersectableWith (OpenInterval r) (OpenInterval r) Source # 
Instance details

Defined in HGeometry.Interval.Internal

(Point_ point 2 r, Fractional r, Ord r) => IsIntersectableWith (LineEQ r) (ClosedLineSegment point) Source # 
Instance details

Defined in HGeometry.LineSegment.Intersection

(Point_ point 2 r, Fractional r, Ord r) => IsIntersectableWith (LineEQ r) (OpenLineSegment point) Source # 
Instance details

Defined in HGeometry.LineSegment.Intersection

(Point_ point 2 r, Num r, Ord r) => HasIntersectionWith (ClosedLineSegment point) (LineSegment AnEndPoint point) Source # 
Instance details

Defined in HGeometry.LineSegment.Intersection

(Point_ point 2 r, Num r, Ord r) => HasIntersectionWith (OpenLineSegment point) (LineSegment AnEndPoint point) Source # 
Instance details

Defined in HGeometry.LineSegment.Intersection

HasEndPoint (HalfOpenInterval r) (EndPoint 'Closed r) Source # 
Instance details

Defined in HGeometry.Interval.HalfOpen

HasStartPoint (HalfOpenInterval r) (EndPoint 'Open r) Source # 
Instance details

Defined in HGeometry.Interval.HalfOpen

(Ord r, IxValue (endPoint r) ~ r, EndPoint_ (endPoint r)) => HasIntersectionWith (ClosedInterval r) (Interval endPoint r) Source # 
Instance details

Defined in HGeometry.Interval.Internal

Methods

intersects :: ClosedInterval r -> Interval endPoint r -> Bool Source #

Ord r => HasIntersectionWith (OpenInterval r) (Interval AnEndPoint r) Source # 
Instance details

Defined in HGeometry.Interval.Internal

Generic (EndPoint et r) Source # 
Instance details

Defined in HGeometry.Interval.EndPoint

Associated Types

type Rep (EndPoint et r) :: Type -> Type #

Methods

from :: EndPoint et r -> Rep (EndPoint et r) x #

to :: Rep (EndPoint et r) x -> EndPoint et r #

Read r => Read (EndPoint 'Closed r) Source # 
Instance details

Defined in HGeometry.Interval.EndPoint

Read r => Read (EndPoint 'Open r) Source # 
Instance details

Defined in HGeometry.Interval.EndPoint

(Show point, Show (ClosedLineSegment point)) => Show (IntersectionOf (ClosedLineSegment point) (Ball point)) Source # 
Instance details

Defined in HGeometry.Ball.CenterAndRadius

Show r => Show (EndPoint 'Closed r) Source # 
Instance details

Defined in HGeometry.Interval.EndPoint

Show r => Show (EndPoint 'Open r) Source # 
Instance details

Defined in HGeometry.Interval.EndPoint

(Eq point, Eq (ClosedLineSegment point)) => Eq (IntersectionOf (ClosedLineSegment point) (Ball point)) Source # 
Instance details

Defined in HGeometry.Ball.CenterAndRadius

Eq r => Eq (EndPoint et r) Source # 
Instance details

Defined in HGeometry.Interval.EndPoint

Methods

(==) :: EndPoint et r -> EndPoint et r -> Bool #

(/=) :: EndPoint et r -> EndPoint et r -> Bool #

Ord r => Ord (EndPoint et r) Source # 
Instance details

Defined in HGeometry.Interval.EndPoint

Methods

compare :: EndPoint et r -> EndPoint et r -> Ordering #

(<) :: EndPoint et r -> EndPoint et r -> Bool #

(<=) :: EndPoint et r -> EndPoint et r -> Bool #

(>) :: EndPoint et r -> EndPoint et r -> Bool #

(>=) :: EndPoint et r -> EndPoint et r -> Bool #

max :: EndPoint et r -> EndPoint et r -> EndPoint et r #

min :: EndPoint et r -> EndPoint et r -> EndPoint et r #

EndPoint_ (EndPoint 'Closed r) Source # 
Instance details

Defined in HGeometry.Interval.EndPoint

EndPoint_ (EndPoint 'Open r) Source # 
Instance details

Defined in HGeometry.Interval.EndPoint

(Point_ point 2 r, Num r, Ord r) => HasIntersectionWith (LineSegment AnEndPoint point) (ClosedLineSegment point) Source # 
Instance details

Defined in HGeometry.LineSegment.Intersection

(Point_ point 2 r, Num r, Ord r) => HasIntersectionWith (LineSegment AnEndPoint point) (OpenLineSegment point) Source # 
Instance details

Defined in HGeometry.LineSegment.Intersection

Ord r => HasIntersectionWith (Point 1 r) (ClosedInterval r) Source # 
Instance details

Defined in HGeometry.Interval.Internal

Methods

intersects :: Point 1 r -> ClosedInterval r -> Bool Source #

Ord r => HasIntersectionWith (Point 1 r) (OpenInterval r) Source # 
Instance details

Defined in HGeometry.Interval.Internal

Methods

intersects :: Point 1 r -> OpenInterval r -> Bool Source #

(Point_ point 2 r, Fractional r, Ord r) => IsIntersectableWith (LinePV 2 r) (ClosedLineSegment point) Source # 
Instance details

Defined in HGeometry.LineSegment.Intersection

(Point_ point 2 r, Fractional r, Ord r) => IsIntersectableWith (LinePV 2 r) (OpenLineSegment point) Source # 
Instance details

Defined in HGeometry.LineSegment.Intersection

Methods

intersect :: LinePV 2 r -> OpenLineSegment point -> Intersection (LinePV 2 r) (OpenLineSegment point) Source #

Ord r => IsIntersectableWith (Point 1 r) (ClosedInterval r) Source # 
Instance details

Defined in HGeometry.Interval.Internal

Ord r => IsIntersectableWith (Point 1 r) (OpenInterval r) Source # 
Instance details

Defined in HGeometry.Interval.Internal

IsEndPoint (EndPoint et r) (EndPoint et r') Source #

Class for types that have _endPoint field.

Instance details

Defined in HGeometry.Interval.EndPoint

Methods

_endPoint :: Lens (EndPoint et r) (EndPoint et r') (IxValue (EndPoint et r)) (IxValue (EndPoint et r')) Source #

Ord r => HasIntersectionWith (Interval AnEndPoint r) (ClosedInterval r) Source # 
Instance details

Defined in HGeometry.Interval.Internal

Ord r => HasIntersectionWith (Interval AnEndPoint r) (OpenInterval r) Source # 
Instance details

Defined in HGeometry.Interval.Internal

type Intersection (ClosedLineSegment point) (Ball point) Source # 
Instance details

Defined in HGeometry.Ball.CenterAndRadius

data IntersectionOf (ClosedLineSegment point) (Ball point) Source # 
Instance details

Defined in HGeometry.Ball.CenterAndRadius

type Intersection (LineEQ r) (LineSegment (EndPoint t) point) Source # 
Instance details

Defined in HGeometry.LineSegment.Intersection

type Rep (EndPoint et r) Source # 
Instance details

Defined in HGeometry.Interval.EndPoint

type Rep (EndPoint et r) = D1 ('MetaData "EndPoint" "HGeometry.Interval.EndPoint" "hgeometry-1.0.0.0-inplace-kernel" 'True) (C1 ('MetaCons "EndPoint" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 r)))
type NumType (EndPoint et r) Source # 
Instance details

Defined in HGeometry.Interval.EndPoint

type NumType (EndPoint et r) = r
type IxValue (EndPoint et r) Source # 
Instance details

Defined in HGeometry.Interval.EndPoint

type IxValue (EndPoint et r) = r
type Intersection (LinePV 2 r) (LineSegment (EndPoint t) point) Source # 
Instance details

Defined in HGeometry.LineSegment.Intersection

type Intersection (LinePV 2 r) (LineSegment (EndPoint t) point)
type Intersection (LineSegment (EndPoint t) point) (LineSegment (EndPoint t) point) Source # 
Instance details

Defined in HGeometry.LineSegment.Intersection

data AnEndPoint r Source #

Data type modelling an endpoint that can both be open and closed.

Constructors

AnEndPoint !EndPointType !r 

Bundled Patterns

pattern AnOpenE :: r -> AnEndPoint r

Constructs an Open endpoint

pattern AnClosedE :: r -> AnEndPoint r

Constructs a closed endpoint

Instances

Instances details
Foldable AnEndPoint Source # 
Instance details

Defined in HGeometry.Interval.EndPoint

Methods

fold :: Monoid m => AnEndPoint m -> m #

foldMap :: Monoid m => (a -> m) -> AnEndPoint a -> m #

foldMap' :: Monoid m => (a -> m) -> AnEndPoint a -> m #

foldr :: (a -> b -> b) -> b -> AnEndPoint a -> b #

foldr' :: (a -> b -> b) -> b -> AnEndPoint a -> b #

foldl :: (b -> a -> b) -> b -> AnEndPoint a -> b #

foldl' :: (b -> a -> b) -> b -> AnEndPoint a -> b #

foldr1 :: (a -> a -> a) -> AnEndPoint a -> a #

foldl1 :: (a -> a -> a) -> AnEndPoint a -> a #

toList :: AnEndPoint a -> [a] #

null :: AnEndPoint a -> Bool #

length :: AnEndPoint a -> Int #

elem :: Eq a => a -> AnEndPoint a -> Bool #

maximum :: Ord a => AnEndPoint a -> a #

minimum :: Ord a => AnEndPoint a -> a #

sum :: Num a => AnEndPoint a -> a #

product :: Num a => AnEndPoint a -> a #

Foldable1 AnEndPoint Source # 
Instance details

Defined in HGeometry.Interval.EndPoint

Methods

fold1 :: Semigroup m => AnEndPoint m -> m #

foldMap1 :: Semigroup m => (a -> m) -> AnEndPoint a -> m #

foldMap1' :: Semigroup m => (a -> m) -> AnEndPoint a -> m #

toNonEmpty :: AnEndPoint a -> NonEmpty a #

maximum :: Ord a => AnEndPoint a -> a #

minimum :: Ord a => AnEndPoint a -> a #

head :: AnEndPoint a -> a #

last :: AnEndPoint a -> a #

foldrMap1 :: (a -> b) -> (a -> b -> b) -> AnEndPoint a -> b #

foldlMap1' :: (a -> b) -> (b -> a -> b) -> AnEndPoint a -> b #

foldlMap1 :: (a -> b) -> (b -> a -> b) -> AnEndPoint a -> b #

foldrMap1' :: (a -> b) -> (a -> b -> b) -> AnEndPoint a -> b #

Traversable AnEndPoint Source # 
Instance details

Defined in HGeometry.Interval.EndPoint

Methods

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

sequenceA :: Applicative f => AnEndPoint (f a) -> f (AnEndPoint a) #

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

sequence :: Monad m => AnEndPoint (m a) -> m (AnEndPoint a) #

Functor AnEndPoint Source # 
Instance details

Defined in HGeometry.Interval.EndPoint

Methods

fmap :: (a -> b) -> AnEndPoint a -> AnEndPoint b #

(<$) :: a -> AnEndPoint b -> AnEndPoint a #

Traversable1 AnEndPoint Source # 
Instance details

Defined in HGeometry.Interval.EndPoint

Methods

traverse1 :: Apply f => (a -> f b) -> AnEndPoint a -> f (AnEndPoint b) Source #

sequence1 :: Apply f => AnEndPoint (f b) -> f (AnEndPoint b) Source #

Generic (AnEndPoint r) Source # 
Instance details

Defined in HGeometry.Interval.EndPoint

Associated Types

type Rep (AnEndPoint r) :: Type -> Type #

Methods

from :: AnEndPoint r -> Rep (AnEndPoint r) x #

to :: Rep (AnEndPoint r) x -> AnEndPoint r #

Read r => Read (AnEndPoint r) Source # 
Instance details

Defined in HGeometry.Interval.EndPoint

Show r => Show (AnEndPoint r) Source # 
Instance details

Defined in HGeometry.Interval.EndPoint

Eq r => Eq (AnEndPoint r) Source # 
Instance details

Defined in HGeometry.Interval.EndPoint

Methods

(==) :: AnEndPoint r -> AnEndPoint r -> Bool #

(/=) :: AnEndPoint r -> AnEndPoint r -> Bool #

Ord r => Ord (AnEndPoint r) Source # 
Instance details

Defined in HGeometry.Interval.EndPoint

EndPoint_ (AnEndPoint r) Source # 
Instance details

Defined in HGeometry.Interval.EndPoint

IsEndPoint (AnEndPoint r) (AnEndPoint r') Source # 
Instance details

Defined in HGeometry.Interval.EndPoint

(Point_ point 2 r, Num r, Ord r) => HasIntersectionWith (ClosedLineSegment point) (LineSegment AnEndPoint point) Source # 
Instance details

Defined in HGeometry.LineSegment.Intersection

(Point_ point 2 r, Num r, Ord r) => HasIntersectionWith (OpenLineSegment point) (LineSegment AnEndPoint point) Source # 
Instance details

Defined in HGeometry.LineSegment.Intersection

(Point_ point 2 r, Fractional r, Ord r) => IsIntersectableWith (LineEQ r) (LineSegment AnEndPoint point) Source # 
Instance details

Defined in HGeometry.LineSegment.Intersection

Ord r => HasIntersectionWith (OpenInterval r) (Interval AnEndPoint r) Source # 
Instance details

Defined in HGeometry.Interval.Internal

(Point_ point d r, Fractional r) => HasOnSegment (LineSegment AnEndPoint point) d Source # 
Instance details

Defined in HGeometry.LineSegment.Internal

Methods

onSegment :: (Ord r, Point_ point0 d r, r ~ NumType (LineSegment AnEndPoint point), d ~ Dimension (LineSegment AnEndPoint point)) => point0 -> LineSegment AnEndPoint point -> Bool Source #

(Point_ point 2 r, Num r) => HasOnSegment (LineSegment AnEndPoint point) 2 Source # 
Instance details

Defined in HGeometry.LineSegment.Internal

Methods

onSegment :: (Ord r, Point_ point0 2 r, r ~ NumType (LineSegment AnEndPoint point), 2 ~ Dimension (LineSegment AnEndPoint point)) => point0 -> LineSegment AnEndPoint point -> Bool Source #

(Point_ point 2 r, Num r, Ord r) => HasIntersectionWith (LineSegment AnEndPoint point) (ClosedLineSegment point) Source # 
Instance details

Defined in HGeometry.LineSegment.Intersection

(Point_ point 2 r, Num r, Ord r) => HasIntersectionWith (LineSegment AnEndPoint point) (OpenLineSegment point) Source # 
Instance details

Defined in HGeometry.LineSegment.Intersection

(Point_ point 2 r, Fractional r, Ord r) => IsIntersectableWith (LinePV 2 r) (LineSegment AnEndPoint point) Source # 
Instance details

Defined in HGeometry.LineSegment.Intersection

Ord r => HasIntersectionWith (Point 1 r) (Interval AnEndPoint r) Source # 
Instance details

Defined in HGeometry.Interval.Internal

Ord r => IsIntersectableWith (Point 1 r) (Interval AnEndPoint r) Source # 
Instance details

Defined in HGeometry.Interval.Internal

Ord r => HasIntersectionWith (Interval AnEndPoint r) (ClosedInterval r) Source # 
Instance details

Defined in HGeometry.Interval.Internal

Ord r => HasIntersectionWith (Interval AnEndPoint r) (OpenInterval r) Source # 
Instance details

Defined in HGeometry.Interval.Internal

Ord r => HasIntersectionWith (Interval AnEndPoint r) (Interval AnEndPoint r) Source # 
Instance details

Defined in HGeometry.Interval.Internal

Ord r => IsIntersectableWith (Interval AnEndPoint r) (Interval AnEndPoint r) Source # 
Instance details

Defined in HGeometry.Interval.Internal

type Rep (AnEndPoint r) Source # 
Instance details

Defined in HGeometry.Interval.EndPoint

type Rep (AnEndPoint r) = D1 ('MetaData "AnEndPoint" "HGeometry.Interval.EndPoint" "hgeometry-1.0.0.0-inplace-kernel" 'False) (C1 ('MetaCons "AnEndPoint" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 EndPointType) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 r)))
type NumType (AnEndPoint r) Source # 
Instance details

Defined in HGeometry.Interval.EndPoint

type NumType (AnEndPoint r) = r
type IxValue (AnEndPoint r) Source # 
Instance details

Defined in HGeometry.Interval.EndPoint

type IxValue (AnEndPoint r) = r
type Intersection (LineEQ r) (LineSegment AnEndPoint point) Source # 
Instance details

Defined in HGeometry.LineSegment.Intersection

type Intersection (LinePV 2 r) (LineSegment AnEndPoint point) Source # 
Instance details

Defined in HGeometry.LineSegment.Intersection

type Intersection (LineSegment AnEndPoint point) (LineSegment AnEndPoint point) Source # 
Instance details

Defined in HGeometry.LineSegment.Intersection

spanIn :: (Point_ point d r, Ord r, IxValue (endPoint point) ~ point, EndPoint_ (endPoint point)) => Getter point r -> LineSegment endPoint point -> Interval AnEndPoint r Source #

Computes the span of the interval in the given direction. Note that the returned interval is a proper interval, i.e. with the start smaller than the end.

>>> spanIn xCoord (ClosedLineSegment (Point2 5 (10 :: Int)) (Point2 20 0))
Interval (AnEndPoint Closed 5) (AnEndPoint Closed 20)
>>> spanIn yCoord (ClosedLineSegment (Point2 5 (10 :: Int)) (Point2 20 0))
Interval (AnEndPoint Closed 0) (AnEndPoint Closed 10)

class IsEndPoint endPoint endPoint => EndPoint_ endPoint where Source #

An endpoint storing values of some type r

Methods

endPointType :: endPoint -> EndPointType Source #

Report the type of the endpoint

mkEndPoint :: IxValue endPoint -> endPoint Source #

constructs a "default" enpoint

data LineLineSegmentIntersection lineSegment Source #

Line x LineSegment intersection

Constructors

Line_x_LineSegment_Point (Point 2 (NumType lineSegment)) 
Line_x_LineSegment_LineSegment lineSegment 

Instances

Instances details
(Show (Point 2 (NumType lineSegment)), Show lineSegment) => Show (LineLineSegmentIntersection lineSegment) Source # 
Instance details

Defined in HGeometry.LineSegment.Intersection

(Eq (Point 2 (NumType lineSegment)), Eq lineSegment) => Eq (LineLineSegmentIntersection lineSegment) Source # 
Instance details

Defined in HGeometry.LineSegment.Intersection

data LineSegmentLineSegmentIntersection lineSegment Source #

LineSegment x LineSegment intersection

Instances

Instances details
(Show (Point 2 (NumType lineSegment)), Show lineSegment) => Show (LineSegmentLineSegmentIntersection lineSegment) Source # 
Instance details

Defined in HGeometry.LineSegment.Intersection

(Eq (Point 2 (NumType lineSegment)), Eq lineSegment) => Eq (LineSegmentLineSegmentIntersection lineSegment) Source # 
Instance details

Defined in HGeometry.LineSegment.Intersection

data HalfLineLineSegmentIntersection point segment Source #

Data type representing the intersection of a HalfLine and a LineSegment

Instances

Instances details
Functor (HalfLineLineSegmentIntersection point) Source # 
Instance details

Defined in HGeometry.LineSegment.Intersection

Generic (HalfLineLineSegmentIntersection point segment) Source # 
Instance details

Defined in HGeometry.LineSegment.Intersection

Associated Types

type Rep (HalfLineLineSegmentIntersection point segment) :: Type -> Type #

(Read point, Read segment) => Read (HalfLineLineSegmentIntersection point segment) Source # 
Instance details

Defined in HGeometry.LineSegment.Intersection

(Show point, Show segment) => Show (HalfLineLineSegmentIntersection point segment) Source # 
Instance details

Defined in HGeometry.LineSegment.Intersection

(Eq point, Eq segment) => Eq (HalfLineLineSegmentIntersection point segment) Source # 
Instance details

Defined in HGeometry.LineSegment.Intersection

(Ord point, Ord segment) => Ord (HalfLineLineSegmentIntersection point segment) Source # 
Instance details

Defined in HGeometry.LineSegment.Intersection

type Rep (HalfLineLineSegmentIntersection point segment) Source # 
Instance details

Defined in HGeometry.LineSegment.Intersection

type Rep (HalfLineLineSegmentIntersection point segment) = D1 ('MetaData "HalfLineLineSegmentIntersection" "HGeometry.LineSegment.Intersection" "hgeometry-1.0.0.0-inplace-kernel" 'False) (C1 ('MetaCons "HalfLine_x_LineSegment_Point" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 point)) :+: C1 ('MetaCons "HalfLine_x_LineSegment_LineSegment" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 segment)))