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

Copyright(C) Frank Staals
Licensesee the LICENSE file
MaintainerFrank Staals
Safe HaskellNone
LanguageHaskell2010

Data.Geometry.Ball

Contents

Description

\(d\)-dimensional Balls and Spheres

Synopsis

A d-dimensional ball

data Ball d p r Source #

A d-dimensional ball.

Constructors

Ball 

Fields

Instances
Arity d => Bifunctor (Ball d) Source # 
Instance details

Defined in Data.Geometry.Ball

Methods

bimap :: (a -> b) -> (c -> d0) -> Ball d a c -> Ball d b d0 #

first :: (a -> b) -> Ball d a c -> Ball d b c #

second :: (b -> c) -> Ball d a b -> Ball d a c #

Arity d => Functor (Ball d p) Source # 
Instance details

Defined in Data.Geometry.Ball

Methods

fmap :: (a -> b) -> Ball d p a -> Ball d p b #

(<$) :: a -> Ball d p b -> Ball d p a #

Floating r => HasDefaultIpeOut (Disk p r) Source # 
Instance details

Defined in Data.Geometry.Ipe.IpeOut

Associated Types

type DefaultIpeOut (Disk p r) :: Type -> Type Source #

Methods

defIO :: IpeOut (Disk p r) (DefaultIpeOut (Disk p r)) (NumType (Disk p r)) Source #

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

Defined in Data.Geometry.Ball

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 #

(Eq r, Eq p, Arity d) => Eq (Ball d p r) Source # 
Instance details

Defined in Data.Geometry.Ball

Methods

(==) :: Ball d p r -> Ball d p r -> Bool #

(/=) :: Ball d p r -> Ball d p r -> Bool #

(Show r, Show p, Arity d) => Show (Ball d p r) Source # 
Instance details

Defined in Data.Geometry.Ball

Methods

showsPrec :: Int -> Ball d p r -> ShowS #

show :: Ball d p r -> String #

showList :: [Ball d p r] -> ShowS #

Generic (Ball d p r) Source # 
Instance details

Defined in Data.Geometry.Ball

Associated Types

type Rep (Ball d p r) :: Type -> Type #

Methods

from :: Ball d p r -> Rep (Ball d p r) x #

to :: Rep (Ball d p r) x -> Ball d p r #

(NFData p, NFData r, Arity d) => NFData (Ball d p r) Source # 
Instance details

Defined in Data.Geometry.Ball

Methods

rnf :: Ball d p r -> () #

(Ord r, Floating r) => IsIntersectableWith (LineSegment 2 p r) (Circle q r) Source # 
Instance details

Defined in Data.Geometry.Ball

Methods

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

intersects :: LineSegment 2 p r -> Circle q r -> Bool Source #

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

type DefaultIpeOut (Disk p r) Source # 
Instance details

Defined in Data.Geometry.Ipe.IpeOut

type DefaultIpeOut (Disk p r) = Path
type IntersectionOf (Line 2 r) (Circle p r) Source #

No intersection, one touching point, or two points

Instance details

Defined in Data.Geometry.Ball

type IntersectionOf (Line 2 r) (Circle p r) = NoIntersection ': (Touching (Point 2 r) ': ((Point 2 r, Point 2 r) ': ([] :: [Type])))
type Rep (Ball d p r) Source # 
Instance details

Defined in Data.Geometry.Ball

type Rep (Ball d p r) = D1 (MetaData "Ball" "Data.Geometry.Ball" "hgeometry-0.8.0.0-2B18HmKepFxHOPvqiUEkND" False) (C1 (MetaCons "Ball" PrefixI True) (S1 (MetaSel (Just "_center") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Point d r :+ p)) :*: S1 (MetaSel (Just "_squaredRadius") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 r)))
type NumType (Ball d p r) Source # 
Instance details

Defined in Data.Geometry.Ball

type NumType (Ball d p r) = r
type Dimension (Ball d p r) Source # 
Instance details

Defined in Data.Geometry.Ball

type Dimension (Ball d p r) = d
type IntersectionOf (LineSegment 2 p r) (Circle q r) Source #

A line segment may not intersect a circle, touch it, or intersect it properly in one or two points.

Instance details

Defined in Data.Geometry.Ball

type IntersectionOf (LineSegment 2 p r) (Circle q r) = NoIntersection ': (Touching (Point 2 r) ': (Point 2 r ': ((Point 2 r, Point 2 r) ': ([] :: [Type]))))

squaredRadius :: forall d p r. Lens' (Ball d p r) r Source #

center :: forall d p r d p. Lens (Ball d p r) (Ball d p r) ((:+) (Point d r) p) ((:+) (Point d r) p) Source #

radius :: Floating r => Lens' (Ball d p r) r Source #

A lens to get/set the radius of a Ball

Constructing Balls

fromDiameter :: (Arity d, Fractional r) => Point d r -> Point d r -> Ball d () r Source #

Given two points on the diameter of the ball, construct a ball.

fromCenterAndPoint :: (Arity d, Num r) => (Point d r :+ p) -> (Point d r :+ p) -> Ball d p r Source #

Construct a ball given the center point and a point p on the boundary.

unitBall :: (Arity d, Num r) => Ball d () r Source #

A d dimensional unit ball centered at the origin.

Querying if a point lies in a ball

inBall :: (Arity d, Ord r, Num r) => Point d r -> Ball d p r -> PointLocationResult Source #

insideBall :: (Arity d, Ord r, Num r) => Point d r -> Ball d p r -> Bool Source #

Test if a point lies strictly inside a ball

>>> (point2 0.5 0.0) `insideBall` unitBall
True
>>> (point2 1 0) `insideBall` unitBall
False
>>> (point2 2 0) `insideBall` unitBall
False

inClosedBall :: (Arity d, Ord r, Num r) => Point d r -> Ball d p r -> Bool Source #

Test if a point lies in or on the ball

onBall :: (Arity d, Ord r, Num r) => Point d r -> Ball d p r -> Bool Source #

Test if a point lies on the boundary of a ball.

>>> (point2 1 0) `onBall` unitBall
True
>>> (point3 1 1 0) `onBall` unitBall
False

type Sphere d p r = Boundary (Ball d p r) Source #

Spheres, i.e. the boundary of a ball.

pattern Sphere :: (Point d r :+ p) -> r -> Sphere d p r Source #

Disks and Circles, aka 2-dimensional Balls and Spheres

type Disk p r = Ball 2 p r Source #

pattern Disk :: (Point 2 r :+ p) -> r -> Disk p r Source #

type Circle p r = Sphere 2 p r Source #

pattern Circle :: (Point 2 r :+ p) -> r -> Circle p r Source #

disk :: (Eq r, Fractional r) => Point 2 r -> Point 2 r -> Point 2 r -> Maybe (Disk () r) Source #

Given three points, get the disk through the three points. If the three input points are colinear we return Nothing

>>> disk (point2 0 10) (point2 10 0) (point2 (-10) 0)
Just (Ball {_center = Point2 [0.0,0.0] :+ (), _squaredRadius = 100.0})

from3Points :: Fractional r => (Point 2 r :+ p) -> (Point 2 r :+ q) -> (Point 2 r :+ s) -> Circle () r Source #

Creates a circle from three points on the boundary

newtype Touching p Source #

Constructors

Touching p 
Instances
Functor Touching Source # 
Instance details

Defined in Data.Geometry.Ball

Methods

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

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

Foldable Touching Source # 
Instance details

Defined in Data.Geometry.Ball

Methods

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

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

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

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

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

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

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

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

toList :: Touching a -> [a] #

null :: Touching a -> Bool #

length :: Touching a -> Int #

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

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

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

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

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

Traversable Touching Source # 
Instance details

Defined in Data.Geometry.Ball

Methods

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

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

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

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

Eq p => Eq (Touching p) Source # 
Instance details

Defined in Data.Geometry.Ball

Methods

(==) :: Touching p -> Touching p -> Bool #

(/=) :: Touching p -> Touching p -> Bool #

Ord p => Ord (Touching p) Source # 
Instance details

Defined in Data.Geometry.Ball

Methods

compare :: Touching p -> Touching p -> Ordering #

(<) :: Touching p -> Touching p -> Bool #

(<=) :: Touching p -> Touching p -> Bool #

(>) :: Touching p -> Touching p -> Bool #

(>=) :: Touching p -> Touching p -> Bool #

max :: Touching p -> Touching p -> Touching p #

min :: Touching p -> Touching p -> Touching p #

Show p => Show (Touching p) Source # 
Instance details

Defined in Data.Geometry.Ball

Methods

showsPrec :: Int -> Touching p -> ShowS #

show :: Touching p -> String #

showList :: [Touching p] -> ShowS #