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.Interval.EndPoint

Description

Endpoints of intervals

Synopsis

Documentation

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

class IsEndPoint endPoint endPoint' where Source #

Types that have an _endPoint field lens.

Methods

_endPoint :: Lens endPoint endPoint' (IxValue endPoint) (IxValue endPoint') Source #

Lens to access the actual data value of the end point

Instances

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

Defined in HGeometry.Interval.EndPoint

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 #

data EndPointType Source #

Possible endpoint types; open or closed

Constructors

Open 
Closed 

Instances

Instances details
Bounded EndPointType Source # 
Instance details

Defined in HGeometry.Interval.EndPoint

Enum EndPointType Source # 
Instance details

Defined in HGeometry.Interval.EndPoint

Generic EndPointType Source # 
Instance details

Defined in HGeometry.Interval.EndPoint

Associated Types

type Rep EndPointType :: Type -> Type #

Read EndPointType Source # 
Instance details

Defined in HGeometry.Interval.EndPoint

Show EndPointType Source # 
Instance details

Defined in HGeometry.Interval.EndPoint

Eq EndPointType Source # 
Instance details

Defined in HGeometry.Interval.EndPoint

Ord EndPointType Source # 
Instance details

Defined in HGeometry.Interval.EndPoint

type Rep EndPointType Source # 
Instance details

Defined in HGeometry.Interval.EndPoint

type Rep EndPointType = D1 ('MetaData "EndPointType" "HGeometry.Interval.EndPoint" "hgeometry-1.0.0.0-inplace-kernel" 'False) (C1 ('MetaCons "Open" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Closed" 'PrefixI 'False) (U1 :: Type -> Type))

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

asAnEndPoint :: EndPoint_ endPoint => endPoint -> AnEndPoint (IxValue endPoint) Source #

Convert the endpoint into a, AnEndPoint