Copyright | (C) Frank Staals |
---|---|
License | see the LICENSE file |
Maintainer | Frank Staals |
Safe Haskell | None |
Language | Haskell2010 |
\(d\)-dimensional Balls and Spheres
Synopsis
- data Ball d p r = Ball {
- _center :: !(Point d r :+ p)
- _squaredRadius :: !r
- squaredRadius :: forall d p r. Lens' (Ball d p r) r
- center :: forall d p r d p. Lens (Ball d p r) (Ball d p r) ((:+) (Point d r) p) ((:+) (Point d r) p)
- radius :: Floating r => Lens' (Ball d p r) r
- fromDiameter :: (Arity d, Fractional r) => Point d r -> Point d r -> Ball d () r
- fromCenterAndPoint :: (Arity d, Num r) => (Point d r :+ p) -> (Point d r :+ p) -> Ball d p r
- unitBall :: (Arity d, Num r) => Ball d () r
- inBall :: (Arity d, Ord r, Num r) => Point d r -> Ball d p r -> PointLocationResult
- insideBall :: (Arity d, Ord r, Num r) => Point d r -> Ball d p r -> Bool
- inClosedBall :: (Arity d, Ord r, Num r) => Point d r -> Ball d p r -> Bool
- onBall :: (Arity d, Ord r, Num r) => Point d r -> Ball d p r -> Bool
- type Sphere d p r = Boundary (Ball d p r)
- pattern Sphere :: (Point d r :+ p) -> r -> Sphere d p r
- _BallSphere :: Iso (Disk p r) (Disk p s) (Circle p r) (Circle p s)
- type Disk p r = Ball 2 p r
- pattern Disk :: (Point 2 r :+ p) -> r -> Disk p r
- type Circle p r = Sphere 2 p r
- _DiskCircle :: Iso (Disk p r) (Disk p s) (Circle p r) (Circle p s)
- pattern Circle :: (Point 2 r :+ p) -> r -> Circle p r
- disk :: (Eq r, Fractional r) => Point 2 r -> Point 2 r -> Point 2 r -> Maybe (Disk () r)
- from3Points :: Fractional r => (Point 2 r :+ p) -> (Point 2 r :+ q) -> (Point 2 r :+ s) -> Circle () r
- newtype Touching p = Touching p
A d-dimensional ball
A d-dimensional ball.
Ball | |
|
Instances
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 #
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
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
Disks and Circles, aka 2-dimensional Balls and Spheres
pattern Disk :: (Point 2 r :+ p) -> r -> Disk p r Source #
Given the center and the squared radius, constructs a disk
_DiskCircle :: Iso (Disk p r) (Disk p s) (Circle p r) (Circle p s) Source #
Iso for converting between Disks and Circles, i.e. forgetting the boundary
pattern Circle :: (Point 2 r :+ p) -> r -> Circle p r Source #
Given the center and the squared radius, constructs a circle
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
Touching p |
Instances
Functor Touching Source # | |
Foldable Touching Source # | |
Defined in Data.Geometry.Ball 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 # elem :: Eq a => a -> Touching a -> Bool # maximum :: Ord a => Touching a -> a # minimum :: Ord a => Touching a -> a # | |
Traversable Touching Source # | |
Eq p => Eq (Touching p) Source # | |
Ord p => Ord (Touching p) Source # | |
Show p => Show (Touching p) Source # | |