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

HGeometry.Plane.LowerEnvelope.Connected

Description

A Representation of the Lower envelope of planes as a bunch of convex regions

Synopsis

Documentation

newtype MinimizationDiagram r vertex plane Source #

A minimization daigram just maps every plane on the lower envelope to the region above which it is minimal. Every plane has at most one such a region.

Constructors

MinimizationDiagram (NEMap plane (Region r vertex)) 

Instances

Instances details
CFunctor (MinimizationDiagram r vertex) Source # 
Instance details

Defined in HGeometry.Plane.LowerEnvelope.Connected.Type

Methods

cmap :: (Dom (MinimizationDiagram r vertex) a, Dom (MinimizationDiagram r vertex) b) => (a -> b) -> MinimizationDiagram r vertex a -> MinimizationDiagram r vertex b Source #

(<$:) :: (Dom (MinimizationDiagram r vertex) a, Dom (MinimizationDiagram r vertex) b) => a -> MinimizationDiagram r vertex b -> MinimizationDiagram r vertex a Source #

Constrained (MinimizationDiagram r vertex) Source # 
Instance details

Defined in HGeometry.Plane.LowerEnvelope.Connected.Type

(Show plane, Show vertex, Show r) => Show (MinimizationDiagram r vertex plane) Source # 
Instance details

Defined in HGeometry.Plane.LowerEnvelope.Connected.Type

Methods

showsPrec :: Int -> MinimizationDiagram r vertex plane -> ShowS #

show :: MinimizationDiagram r vertex plane -> String #

showList :: [MinimizationDiagram r vertex plane] -> ShowS #

(Eq plane, Eq vertex, Eq r) => Eq (MinimizationDiagram r vertex plane) Source # 
Instance details

Defined in HGeometry.Plane.LowerEnvelope.Connected.Type

Methods

(==) :: MinimizationDiagram r vertex plane -> MinimizationDiagram r vertex plane -> Bool #

(/=) :: MinimizationDiagram r vertex plane -> MinimizationDiagram r vertex plane -> Bool #

type Dom (MinimizationDiagram r vertex) plane Source # 
Instance details

Defined in HGeometry.Plane.LowerEnvelope.Connected.Type

type Dom (MinimizationDiagram r vertex) plane = (Ord plane, NumType plane ~ r)
type Dimension (MinimizationDiagram r vertex plane) Source # 
Instance details

Defined in HGeometry.Plane.LowerEnvelope.Connected.Type

type Dimension (MinimizationDiagram r vertex plane) = 2
type NumType (MinimizationDiagram r vertex plane) Source # 
Instance details

Defined in HGeometry.Plane.LowerEnvelope.Connected.Type

type NumType (MinimizationDiagram r vertex plane) = r

asMap :: MinimizationDiagram r vertex plane -> NEMap plane (Region r vertex) Source #

Get the underlying Map that relates every plane in the envelope to its projected region

mapVertices :: (vertex -> vertex') -> MinimizationDiagram r vertex plane -> MinimizationDiagram r vertex' plane Source #

Apply some mapping function to the vertex data of each vertex

data Region r point Source #

A region in the minimization diagram. The boundary is given in CCW order; i.e. the region is to the left of the boundary.

Constructors

Bounded (Cyclic NonEmpty point) 
Unbounded 

Fields

  • (Vector 2 r)

    vector indicating the direction of the unbounded edge incident to the first vertex. Note that this vector thus points INTO vertex v.

  • (NonEmpty point)

    the vertices in CCW order,

  • (Vector 2 r)

    the vector indicating the direction of the unbounded edge incident to the last vertex. The vector points away from the vertex (i.e. towards +infty).

Instances

Instances details
Functor (Region r) Source # 
Instance details

Defined in HGeometry.Plane.LowerEnvelope.Connected.Type

Methods

fmap :: (a -> b) -> Region r a -> Region r b #

(<$) :: a -> Region r b -> Region r a #

Foldable (Region r) Source # 
Instance details

Defined in HGeometry.Plane.LowerEnvelope.Connected.Type

Methods

fold :: Monoid m => Region r m -> m #

foldMap :: Monoid m => (a -> m) -> Region r a -> m #

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

foldr :: (a -> b -> b) -> b -> Region r a -> b #

foldr' :: (a -> b -> b) -> b -> Region r a -> b #

foldl :: (b -> a -> b) -> b -> Region r a -> b #

foldl' :: (b -> a -> b) -> b -> Region r a -> b #

foldr1 :: (a -> a -> a) -> Region r a -> a #

foldl1 :: (a -> a -> a) -> Region r a -> a #

toList :: Region r a -> [a] #

null :: Region r a -> Bool #

length :: Region r a -> Int #

elem :: Eq a => a -> Region r a -> Bool #

maximum :: Ord a => Region r a -> a #

minimum :: Ord a => Region r a -> a #

sum :: Num a => Region r a -> a #

product :: Num a => Region r a -> a #

Traversable (Region r) Source # 
Instance details

Defined in HGeometry.Plane.LowerEnvelope.Connected.Type

Methods

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

sequenceA :: Applicative f => Region r (f a) -> f (Region r a) #

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

sequence :: Monad m => Region r (m a) -> m (Region r a) #

(Show point, Show r) => Show (Region r point) Source # 
Instance details

Defined in HGeometry.Plane.LowerEnvelope.Connected.Type

Methods

showsPrec :: Int -> Region r point -> ShowS #

show :: Region r point -> String #

showList :: [Region r point] -> ShowS #

(Eq point, Eq r) => Eq (Region r point) Source # 
Instance details

Defined in HGeometry.Plane.LowerEnvelope.Connected.Type

Methods

(==) :: Region r point -> Region r point -> Bool #

(/=) :: Region r point -> Region r point -> Bool #

type Dimension (Region r point) Source # 
Instance details

Defined in HGeometry.Plane.LowerEnvelope.Connected.Type

type Dimension (Region r point) = Dimension point
type NumType (Region r point) Source # 
Instance details

Defined in HGeometry.Plane.LowerEnvelope.Connected.Type

type NumType (Region r point) = r

toConvexPolygonIn :: (Rectangle_ rectangle corner, Point_ corner 2 r, Point_ point 2 r, Ord r, Fractional r) => rectangle -> Region r point -> Either (ConvexPolygonF NonEmpty point) (ConvexPolygonF NonEmpty (OriginalOrExtra point (Point 2 r))) Source #

Computes a convex polygon corresponding to the region.

pre: the bounding box (strictly) contains all vertices in its interior

intersectionPoint :: (Plane_ plane r, Ord r, Fractional r) => Three plane -> Maybe (Point 3 r) Source #

Computes there the three planes intersect

intersectionLine :: (Plane_ plane r, Fractional r, Eq r) => plane -> plane -> Maybe (VerticalOrLineEQ r) Source #

Given two planes, computes the line in which they intersect.

intersectionVector :: (Plane_ plane r, Ord r, Fractional r) => plane -> plane -> Maybe (Vector 2 r) Source #

Computes the direction vector v of the directed line l in which the two planes h and h' intersect, and so that h will be to the left of the directed line

type VertexForm (map :: Type -> Type -> k) r plane = map (Point 3 r) (Definers plane) Source #

The vertices of a lower envelope is just a Map with every vertex its definers, i.e. the planes that define the vertex in CCW order around it.

data Definers plane Source #

in CCW order, starting with the plane that is minimal at the vertical up direction from their common vertex.

Instances

Instances details
Foldable1 Definers Source # 
Instance details

Defined in HGeometry.Plane.LowerEnvelope.Connected.VertexForm

Methods

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

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

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

toNonEmpty :: Definers a -> NonEmpty a #

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

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

head :: Definers a -> a #

last :: Definers a -> a #

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

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

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

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

Functor Definers Source # 
Instance details

Defined in HGeometry.Plane.LowerEnvelope.Connected.VertexForm

Methods

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

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

Foldable Definers Source # 
Instance details

Defined in HGeometry.Plane.LowerEnvelope.Connected.VertexForm

Methods

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

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

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

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

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

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

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

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

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

toList :: Definers a -> [a] #

null :: Definers a -> Bool #

length :: Definers a -> Int #

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

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

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

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

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

Show plane => Show (Definers plane) Source # 
Instance details

Defined in HGeometry.Plane.LowerEnvelope.Connected.VertexForm

Methods

showsPrec :: Int -> Definers plane -> ShowS #

show :: Definers plane -> String #

showList :: [Definers plane] -> ShowS #

Eq plane => Eq (Definers plane) Source # 
Instance details

Defined in HGeometry.Plane.LowerEnvelope.Connected.VertexForm

Methods

(==) :: Definers plane -> Definers plane -> Bool #

(/=) :: Definers plane -> Definers plane -> Bool #

Ord plane => Ord (Definers plane) Source # 
Instance details

Defined in HGeometry.Plane.LowerEnvelope.Connected.VertexForm

Methods

compare :: Definers plane -> Definers plane -> Ordering #

(<) :: Definers plane -> Definers plane -> Bool #

(<=) :: Definers plane -> Definers plane -> Bool #

(>) :: Definers plane -> Definers plane -> Bool #

(>=) :: Definers plane -> Definers plane -> Bool #

max :: Definers plane -> Definers plane -> Definers plane #

min :: Definers plane -> Definers plane -> Definers plane #

fromCCWList :: NonEmpty plane -> Definers plane Source #

Given the planes in order, starting with the one that is closest in the up direction, construct the Definers.

definers :: (Plane_ plane r, Ord r, Fractional r) => Three plane -> Maybe (Point 3 r, Definers plane) Source #

Smart constructor for creating the definers of three planes

fromVertexForm :: (Plane_ plane r, Ord plane, Ord r, Fractional r, Show r, Show plane, HasDefiners vertex plane, Ord vertex) => NEMap (Point 3 r) vertex -> MinimizationDiagram r (Point 2 r :+ vertex) plane Source #

Given the vertices of the lower envelope; compute the minimization diagram.

\(O(h\log h)\) assuming that the input is non-degenerate.

mergeDefiners :: (Plane_ plane r, Eq plane, Ord r, Fractional r, Show plane, Show r) => Point 3 r -> Definers plane -> Definers plane -> Definers plane Source #

Merge two lists of definers.

\(O(n\log n)\), where \(n\) is the total number of planes involved.

fromVertexFormIn :: (Plane_ plane r, Ord plane, Ord r, Fractional r, Show r, Show plane, HasDefiners vertexData plane, Point_ corner 2 r, Ord vertexData, Show r, Show corner) => Triangle corner -> NEMap (Point 3 r) vertexData -> NEMap plane (BoundedRegion r (Point 2 r :+ vertexData) (Point 2 r)) Source #

Pre: the triangle is big enough to contain all vertices of the lower envelope

type BoundedRegion (r :: k) vertex corner = ConvexPolygonF NonEmpty (OriginalOrExtra vertex corner) Source #

extraPoints :: (Triangle_ triangle corner, Point_ corner 2 r, Point_ point 2 r, Fractional r, Ord r, IsIntersectableWith (HalfLine point) (ClosedLineSegment corner), Intersection (HalfLine point) (ClosedLineSegment corner) ~ Maybe (HalfLineLineSegmentIntersection (Point 2 r) (ClosedLineSegment corner)), HasOuterBoundary triangle, Eq (VertexIx triangle), Show point, Show r, Show corner, Show triangle) => HalfLine point -> HalfLine point -> triangle -> NonEmpty (Point 2 r) Source #

computes the extra vertices that we have to insert to make an unbounded region bounded