Copyright | (C) Frank Staals |
---|---|
License | see the LICENSE file |
Maintainer | Frank Staals |
Safe Haskell | None |
Language | GHC2021 |
HGeometry.Plane.LowerEnvelope.Connected
Description
A Representation of the Lower envelope of planes as a bunch of convex regions
Synopsis
- newtype MinimizationDiagram r vertex plane = MinimizationDiagram (NEMap plane (Region r vertex))
- asMap :: MinimizationDiagram r vertex plane -> NEMap plane (Region r vertex)
- mapVertices :: (vertex -> vertex') -> MinimizationDiagram r vertex plane -> MinimizationDiagram r vertex' plane
- data Region r vertex
- = BoundedRegion (ConvexPolygonF (Cyclic NonEmpty) vertex)
- | UnboundedRegion (UnboundedConvexRegionF r NonEmpty vertex)
- data MDVertex r plane = MDVertex (Point 3 r) (Definers plane)
- location :: forall r1 plane r2 f. Functor f => (Point 3 r1 -> f (Point 3 r2)) -> MDVertex r1 plane -> f (MDVertex r2 plane)
- toConvexPolygonIn :: (Rectangle_ rectangle corner, Point_ corner 2 r, Point_ point 2 r, Ord r, Fractional r) => rectangle -> Region r point -> Either (ConvexPolygonF (Cyclic NonEmpty) point) (ConvexPolygonF (Cyclic NonEmpty) (OriginalOrExtra point (Point 2 r)))
- intersectionPoint :: (Plane_ plane r, Ord r, Fractional r) => Three plane -> Maybe (Point 3 r)
- intersectionLine :: (Plane_ plane r, Fractional r, Eq r) => plane -> plane -> Maybe (VerticalOrLineEQ r)
- intersectionVector :: (Plane_ plane r, Ord r, Fractional r) => plane -> plane -> Maybe (Vector 2 r)
- type VertexForm (map :: Type -> Type -> k) r plane = map (Point 3 r) (Definers plane)
- data Definers plane
- fromCCWList :: NonEmpty plane -> Definers plane
- definers :: (Plane_ plane r, Ord r, Fractional r) => Three plane -> Maybe (Point 3 r, Definers plane)
- type ClippedBoundedRegion (r :: k) vertex corner = ConvexPolygonF (Cyclic NonEmpty) (OriginalOrExtra vertex corner)
- fromVertexForm :: (Plane_ plane r, Ord plane, Ord r, Fractional r, Show r, Show plane) => NEMap (Point 3 r) (Definers plane) -> MinimizationDiagram r (MDVertex r plane) plane
- mergeDefiners :: (Plane_ plane r, Eq plane, Ord r, Fractional r, Show plane, Show r) => Point 3 r -> Definers plane -> Definers plane -> Definers plane
- fromVertexFormIn :: (Plane_ plane r, Ord plane, Ord r, Fractional r, Show r, Show plane, Point_ corner 2 r, Show r, Show corner) => Triangle corner -> NEMap (Point 3 r) (Definers plane) -> NEMap plane (ClippedBoundedRegion r (MDVertex r plane) (Point 2 r))
- 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)
- module HGeometry.Plane.LowerEnvelope.Connected.BruteForce
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
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
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
BoundedRegion (ConvexPolygonF (Cyclic NonEmpty) vertex) | |
UnboundedRegion (UnboundedConvexRegionF r NonEmpty vertex) |
Instances
Functor (Region r) Source # | |
Foldable (Region r) Source # | |
Defined in HGeometry.Plane.LowerEnvelope.Connected.Region 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 # elem :: Eq a => a -> Region r a -> Bool # maximum :: Ord a => Region r a -> a # minimum :: Ord a => Region r a -> a # | |
Traversable (Region r) Source # | |
(Point_ vertex 2 r, Point_ corner 2 r, Ord r, Fractional r) => HasIntersectionWith (Triangle corner) (Region r vertex) | |
Defined in HGeometry.Plane.LowerEnvelope.Clipped.Type Methods intersects :: Triangle corner -> Region r vertex -> Bool | |
(Point_ vertex 2 r, Point_ corner 2 r, Ord r, Fractional r) => IsIntersectableWith (Triangle corner) (Region r vertex) | |
Defined in HGeometry.Plane.LowerEnvelope.Clipped.Type | |
(Show r, Show vertex, Point_ vertex 2 r) => Show (Region r vertex) Source # | |
(Eq r, Eq vertex) => Eq (Region r vertex) Source # | |
type Intersection (Triangle corner) (Region r vertex) | Intersecting Triangles and Region in a MinimizationDiagram yields a clipped cell. |
Defined in HGeometry.Plane.LowerEnvelope.Clipped.Type | |
type Dimension (Region r point) Source # | |
Defined in HGeometry.Plane.LowerEnvelope.Connected.Region type Dimension (Region r point) = Dimension point | |
type NumType (Region r point) Source # | |
Defined in HGeometry.Plane.LowerEnvelope.Connected.Region type NumType (Region r point) = r |
data MDVertex r plane Source #
A vertex of the minimzation Diagram that is defined by the intersection of a number of planes.
Note that we interpet this vertex as a 2-dimensional thing.
Instances
Functor (MDVertex r) Source # | |
Foldable (MDVertex r) Source # | |
Defined in HGeometry.Plane.LowerEnvelope.Connected.Region Methods fold :: Monoid m => MDVertex r m -> m # foldMap :: Monoid m => (a -> m) -> MDVertex r a -> m # foldMap' :: Monoid m => (a -> m) -> MDVertex r a -> m # foldr :: (a -> b -> b) -> b -> MDVertex r a -> b # foldr' :: (a -> b -> b) -> b -> MDVertex r a -> b # foldl :: (b -> a -> b) -> b -> MDVertex r a -> b # foldl' :: (b -> a -> b) -> b -> MDVertex r a -> b # foldr1 :: (a -> a -> a) -> MDVertex r a -> a # foldl1 :: (a -> a -> a) -> MDVertex r a -> a # toList :: MDVertex r a -> [a] # null :: MDVertex r a -> Bool # length :: MDVertex r a -> Int # elem :: Eq a => a -> MDVertex r a -> Bool # maximum :: Ord a => MDVertex r a -> a # minimum :: Ord a => MDVertex r a -> a # | |
(Show r, Show plane) => Show (MDVertex r plane) Source # | |
(Eq r, Eq plane) => Eq (MDVertex r plane) Source # | |
(Ord r, Ord plane) => Ord (MDVertex r plane) Source # | |
Defined in HGeometry.Plane.LowerEnvelope.Connected.Region Methods compare :: MDVertex r plane -> MDVertex r plane -> Ordering # (<) :: MDVertex r plane -> MDVertex r plane -> Bool # (<=) :: MDVertex r plane -> MDVertex r plane -> Bool # (>) :: MDVertex r plane -> MDVertex r plane -> Bool # (>=) :: MDVertex r plane -> MDVertex r plane -> Bool # max :: MDVertex r plane -> MDVertex r plane -> MDVertex r plane # min :: MDVertex r plane -> MDVertex r plane -> MDVertex r plane # | |
Num r => IsBoxable (MDVertex r plane) Source # | |
Affine_ (MDVertex r plane) 2 r Source # | |
Num r => Point_ (MDVertex r plane) 2 r Source # | |
HasCoordinates (MDVertex r plane) (MDVertex r plane) Source # | |
Defined in HGeometry.Plane.LowerEnvelope.Connected.Region Methods coordinates :: IndexedTraversal1 Int (MDVertex r plane) (MDVertex r plane) (NumType (MDVertex r plane)) (NumType (MDVertex r plane)) # | |
HasVector (MDVertex r plane) (MDVertex r plane) Source # | |
type Dimension (MDVertex r plane) Source # | |
Defined in HGeometry.Plane.LowerEnvelope.Connected.Region type Dimension (MDVertex r plane) = 2 | |
type NumType (MDVertex r plane) Source # | |
Defined in HGeometry.Plane.LowerEnvelope.Connected.Region type NumType (MDVertex r plane) = r |
location :: forall r1 plane r2 f. Functor f => (Point 3 r1 -> f (Point 3 r2)) -> MDVertex r1 plane -> f (MDVertex r2 plane) Source #
toConvexPolygonIn :: (Rectangle_ rectangle corner, Point_ corner 2 r, Point_ point 2 r, Ord r, Fractional r) => rectangle -> Region r point -> Either (ConvexPolygonF (Cyclic NonEmpty) point) (ConvexPolygonF (Cyclic 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.
in CCW order, starting with the plane that is minimal at the vertical up direction from their common vertex.
Instances
Foldable1 Definers Source # | |
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 # 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 # | |
Foldable Definers Source # | |
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 # elem :: Eq a => a -> Definers a -> Bool # maximum :: Ord a => Definers a -> a # minimum :: Ord a => Definers a -> a # | |
Show plane => Show (Definers plane) Source # | |
Eq plane => Eq (Definers plane) Source # | |
Ord plane => Ord (Definers plane) Source # | |
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 # |
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
type ClippedBoundedRegion (r :: k) vertex corner = ConvexPolygonF (Cyclic NonEmpty) (OriginalOrExtra vertex corner) Source #
A Convex bounded region, which may be clipped using vertices of type corner
.
fromVertexForm :: (Plane_ plane r, Ord plane, Ord r, Fractional r, Show r, Show plane) => NEMap (Point 3 r) (Definers plane) -> MinimizationDiagram r (MDVertex r plane) 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, Point_ corner 2 r, Show r, Show corner) => Triangle corner -> NEMap (Point 3 r) (Definers plane) -> NEMap plane (ClippedBoundedRegion r (MDVertex r plane) (Point 2 r)) Source #
Pre: the triangle is big enough to contain all vertices of the lower envelope
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