hgeometry-0.13: Geometric Algorithms, Data structures, and Data types.
Copyright(C) Frank Staals
Licensesee the LICENSE file
MaintainerFrank Staals
Safe HaskellNone
LanguageHaskell2010

Algorithms.Geometry.SmallestEnclosingBall

Description

Types to represent the smallest enclosing disk of a set of points in \(\mathbb{R}^2\)

Synopsis

Documentation

data DiskResult p r Source #

The result of a smallest enclosing disk computation: The smallest ball and the points defining it

Constructors

DiskResult 

Instances

Instances details
(Eq r, Eq p) => Eq (DiskResult p r) Source # 
Instance details

Defined in Algorithms.Geometry.SmallestEnclosingBall.Types

Methods

(==) :: DiskResult p r -> DiskResult p r -> Bool #

(/=) :: DiskResult p r -> DiskResult p r -> Bool #

(Show r, Show p) => Show (DiskResult p r) Source # 
Instance details

Defined in Algorithms.Geometry.SmallestEnclosingBall.Types

Methods

showsPrec :: Int -> DiskResult p r -> ShowS #

show :: DiskResult p r -> String #

showList :: [DiskResult p r] -> ShowS #

enclosingDisk :: forall p r. Lens' (DiskResult p r) (Disk () r) Source #

definingPoints :: forall p r p. Lens (DiskResult p r) (DiskResult p r) (TwoOrThree ((:+) (Point 2 r) p)) (TwoOrThree ((:+) (Point 2 r) p)) Source #

data TwoOrThree a Source #

List of two or three elements

Constructors

Two !a !a 
Three !a !a !a 

Instances

Instances details
Functor TwoOrThree Source # 
Instance details

Defined in Algorithms.Geometry.SmallestEnclosingBall.Types

Methods

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

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

Foldable TwoOrThree Source # 
Instance details

Defined in Algorithms.Geometry.SmallestEnclosingBall.Types

Methods

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

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

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

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

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

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

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

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

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

toList :: TwoOrThree a -> [a] #

null :: TwoOrThree a -> Bool #

length :: TwoOrThree a -> Int #

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

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

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

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

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

Eq a => Eq (TwoOrThree a) Source # 
Instance details

Defined in Algorithms.Geometry.SmallestEnclosingBall.Types

Methods

(==) :: TwoOrThree a -> TwoOrThree a -> Bool #

(/=) :: TwoOrThree a -> TwoOrThree a -> Bool #

Ord a => Ord (TwoOrThree a) Source # 
Instance details

Defined in Algorithms.Geometry.SmallestEnclosingBall.Types

Read a => Read (TwoOrThree a) Source # 
Instance details

Defined in Algorithms.Geometry.SmallestEnclosingBall.Types

Show a => Show (TwoOrThree a) Source # 
Instance details

Defined in Algorithms.Geometry.SmallestEnclosingBall.Types

twoOrThreeFromList :: [a] -> Either String (TwoOrThree a) Source #

Construct datatype from list with exactly two or three elements.