Skip to content

Commit

Permalink
read polygons with holes
Browse files Browse the repository at this point in the history
  • Loading branch information
noinia committed Dec 22, 2024
1 parent e3c363e commit 113ef35
Show file tree
Hide file tree
Showing 4 changed files with 54 additions and 9 deletions.
3 changes: 2 additions & 1 deletion hgeometry/ipe/src/Ipe.hs
Original file line number Diff line number Diff line change
Expand Up @@ -71,7 +71,8 @@ module Ipe(
, _asPolyLine
, _asSimplePolygon
, _asConvexPolygon
-- , _asSomePolygon, _asSimplePolygon, _asMultiPolygon
, _asPolygonalDomain

-- *** Dealing with Attributes
, _withAttrs
-- ** Default readers
Expand Down
26 changes: 25 additions & 1 deletion hgeometry/ipe/src/Ipe/FromIpe.hs
Original file line number Diff line number Diff line change
Expand Up @@ -21,7 +21,9 @@ module Ipe.FromIpe(
, _asPolyLine
, _asSimplePolygon
, _asConvexPolygon
-- , _asSomePolygon, _asSimplePolygon, _asMultiPolygon
, _asPolygonalDomain

, toPolygonalDomain

-- * Dealing with Attributes
, _withAttrs
Expand All @@ -36,24 +38,29 @@ module Ipe.FromIpe(
import Control.Lens hiding (Simple)
import Data.Kind (Type)
import qualified Data.Sequence as Seq
import Data.Vector.NonEmpty (NonEmptyVector)
import HGeometry.Ball
import HGeometry.Box
import qualified HGeometry.Box as Box
import HGeometry.Cyclic
import HGeometry.Ellipse (Ellipse, _EllipseCircle)
import HGeometry.Ext
import HGeometry.Foldable.Util
import HGeometry.LineSegment
import HGeometry.Number.Radical
import HGeometry.Point
import qualified HGeometry.PolyLine as PolyLine
import HGeometry.Polygon.Class
import HGeometry.Polygon.Convex
import HGeometry.Polygon.Simple
import HGeometry.Polygon.WithHoles
import HGeometry.Properties
import HGeometry.Triangle
import Ipe.Path
import Ipe.Reader
import Ipe.Types
import System.OsPath
import Witherable

--------------------------------------------------------------------------------

Expand Down Expand Up @@ -127,6 +134,23 @@ _asSimplePolygon = prism' polygonToPath pathToPolygon
_asConvexPolygon :: (Num r, Ord r) => Prism' (Path r) (ConvexPolygon (Point 2 r))
_asConvexPolygon = _asSimplePolygon._ConvexPolygon

-- | Convert to a polygonal domain
_asPolygonalDomain :: Prism' (Path r) (PolygonalDomain (Point 2 r))
_asPolygonalDomain = prism' toPath toDomain
where
toPath (PolygonalDomain outer' holes') =
Path $ (pathPiece outer' Seq.<| fromFoldable (fmap pathPiece holes'))
pathPiece = PolygonPath AsIs

toDomain path = over theHoles fromFoldable <$> toPolygonalDomain path

-- | Convert to a path to a Polygonal Domain
toPolygonalDomain :: Path r
-> Maybe (PolygonalDomainF Seq.Seq (Cyclic NonEmptyVector) (Point 2 r))
toPolygonalDomain path = case mapMaybe (preview (_PolygonPath._2)) (path^.pathSegments) of
outer' Seq.:<| holes' -> Just $ PolygonalDomain outer' holes'
_ -> Nothing

-- | Tries to convert a path into a rectangle.
_asRectangle :: forall r. (Num r, Ord r) => Prism' (Path r) (Rectangle (Point 2 r))
_asRectangle = prism' rectToPath pathToRect
Expand Down
5 changes: 4 additions & 1 deletion hgeometry/src/HGeometry/PlaneGraph/Type.hs
Original file line number Diff line number Diff line change
Expand Up @@ -114,13 +114,14 @@ instance DiGraph_ (PlaneGraph s v e f) where
twinDartOf d = twinOf d . to Just
outgoingDartsOf v = _PlanarGraph.outgoingDartsOf v

{-
instance ConstructableDiGraph_ (PlaneGraph s v e f) where
type DiGraphFromAdjListExtraConstraints (PlaneGraph s v e f) h = (f ~ (), Foldable1 h)
-- | The vertices are expected to have their adjacencies in CCW order.
diGraphFromAdjacencyLists = PlaneGraph . diGraphFromAdjacencyLists
-- TODO: we should probably use some toEmbedding here as well I think

-}

instance BidirGraph_ (PlaneGraph s v e f) where
twinOf d = to $ const (PG.twin d)
Expand Down Expand Up @@ -151,11 +152,13 @@ instance ( Point_ v 2 (NumType v)
neighboursOf u = _PlanarGraph.neighboursOf u
incidentEdgesOf u = _PlanarGraph.incidentEdgesOf u

{-
instance ( Point_ v 2 (NumType v)
, Ord (NumType v), Num (NumType v)
) => ConstructableGraph_ (PlaneGraph s v e f) where
type GraphFromAdjListExtraConstraints (PlaneGraph s v e f) h = (f ~ (), Foldable1 h)
fromAdjacencyLists = fromEmbedding . toEmbedding
-}

instance ( Point_ v 2 (NumType v)
, Ord (NumType v), Num (NumType v)
Expand Down
29 changes: 23 additions & 6 deletions todo.org
Original file line number Diff line number Diff line change
Expand Up @@ -126,13 +126,30 @@ initial run that actually triangulates the whole world:

cabal run hgeometry-examples:hgeometry-triangulateworld -- -i -o 130.82s user 0.50s system 99% cpu 2:12.23 total




** TODO verify fromPoints

i.e. add a test that makes sure that the cyclic zero's are correct,
i.e. that

myPoly :: SimplePolygon (Point 2 R)
myPoly = fromJust . fromPoints $
read @[Point 2 R] "[Point2 0 0,Point2 26 37.1,Point2 7.1 45.2,Point2 (-6.6) 39,Point2 (-1.9) 15.1,Point2 (-1.4) 12.7,Point2 0 0]"

sanitizes the two Point2 0 0's at the end and the start



** TODO polygons with holes
*** DONE represent polygons with holes
*** TODO inpolygon test
make sure we can report in which hole we are as well
*** TODO some tests
*** TODO render them to ipe
*** DONE render them to ipe
*** TODO intersect with a line or with a segment

* DONE avoid binary files in the tests ; replace them with json files or so
(in particular, the arbitrary instances for polygon)

Expand All @@ -148,7 +165,7 @@ make sure we can report in which hole we are as well
* TODO arrangement
** TODO line-segment-intersection sweep
** TODO planar subdivision
*** TODO plane graph
*** DONE plane graph

* TODO 3d-lower-envelope
** TODO naive
Expand Down Expand Up @@ -193,8 +210,8 @@ guaranteed to appear: )

** TODO 3d convex hull

** TODO render faces as polygons
** TODO 3d export of the lower envelope
** DONE render faces as polygons
** DONE 3d export of the lower envelope

* DONE Convex polygons
** DONE binary search extremal direction
Expand Down Expand Up @@ -226,8 +243,8 @@ guaranteed to appear: )
** TODO linear programming (RIC)

* TODO delaunay triangulation
* TODO voronoi diagram
** TODO all colinear points
* DONE voronoi diagram
** DONE all colinear points
* DONE closest pair
* DONE minkowski-sum
** DONE fix testcases
Expand Down

0 comments on commit 113ef35

Please sign in to comment.