Skip to content

Commit

Permalink
Merge pull request #195 from noinia/maintenance-abstract
Browse files Browse the repository at this point in the history
Making some of the types abstract partially Adresses #194
  • Loading branch information
noinia authored May 3, 2022
2 parents e686ab0 + ee0a8f4 commit 8bebc3d
Show file tree
Hide file tree
Showing 5 changed files with 96 additions and 23 deletions.
4 changes: 1 addition & 3 deletions hgeometry-ipe/src/Ipe/Attributes.hs
Original file line number Diff line number Diff line change
Expand Up @@ -151,7 +151,6 @@ instance Semigroup (Attr f l) where

instance Monoid (Attr f l) where
mempty = NoAttr
mappend = (<>)

--------------------------------------------------------------------------------
-- * Attributes
Expand All @@ -175,10 +174,9 @@ instance ( ReifyConstraint Eq (Attr f) ats, RecordToList ats

instance RecApplicative ats => Monoid (Attributes f ats) where
mempty = Attrs $ rpure mempty
a `mappend` b = a <> b

instance Semigroup (Attributes f ats) where
(Attrs as) <> (Attrs bs) = Attrs $ zipRecsWith mappend as bs
(Attrs as) <> (Attrs bs) = Attrs $ zipRecsWith (<>) as bs

-- | Traverse implementation for Attrs
traverseAttrs :: Applicative h
Expand Down
12 changes: 6 additions & 6 deletions hgeometry/src/Algorithms/Geometry/DelaunayTriangulation/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -27,16 +27,16 @@ module Algorithms.Geometry.DelaunayTriangulation.Types
import Control.Lens
import qualified Data.CircularList as C
import Data.Ext
import Geometry.Point
import Geometry.Properties
import Geometry.PlanarSubdivision
import qualified Data.IntMap.Strict as IM
import qualified Data.Map as M
import Geometry.PlanarSubdivision
import Geometry.Point
import Geometry.Properties
-- import qualified Data.Map.Strict as SM
import qualified Data.PlaneGraph as PG
import qualified Data.PlaneGraph as PG
import qualified Data.PlanarGraph as PPG
import qualified Data.Vector as V

import Data.PlaneGraph.Core (PlaneGraph(..))

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

Expand Down Expand Up @@ -124,7 +124,7 @@ toPlanarSubdivision = fromPlaneGraph . toPlaneGraph
--
-- running time: \(O(n)\).
toPlaneGraph :: forall s p r. Triangulation p r -> PG.PlaneGraph s p () () r
toPlaneGraph tr = PG.PlaneGraph $ g&PPG.vertexData .~ vtxData
toPlaneGraph tr = PlaneGraph $ g&PPG.vertexData .~ vtxData
where
g = PPG.fromAdjacencyLists . V.toList . V.imap f $ tr^.neighbours
f i adj = (VertexId i, C.leftElements $ VertexId <$> adj) -- report in CCW order
Expand Down
2 changes: 1 addition & 1 deletion hgeometry/src/Data/PlaneGraph.hs
Original file line number Diff line number Diff line change
Expand Up @@ -13,7 +13,7 @@
--------------------------------------------------------------------------------
module Data.PlaneGraph( -- $setup
-- * The PlaneGraph data type
PlaneGraph(PlaneGraph), graph
PlaneGraph, graph
, PlanarGraph
, VertexData(VertexData), vData, location, vtxDataToExt

Expand Down
21 changes: 11 additions & 10 deletions hgeometry/src/Geometry/Arrangement.hs
Original file line number Diff line number Diff line change
Expand Up @@ -8,18 +8,19 @@
-- Data type for representing an Arrangement of lines in \(\mathbb{R}^2\).
--
--------------------------------------------------------------------------------
module Geometry.Arrangement( Arrangement(..)
, inputLines, subdivision, boundedArea, unboundedIntersections
, ArrangementBoundary
module Geometry.Arrangement
( Arrangement
, inputLines, subdivision, boundedArea, unboundedIntersections
, ArrangementBoundary

, constructArrangement
, constructArrangementInBox
, constructArrangementInBox'
, constructArrangement
, constructArrangementInBox
, constructArrangementInBox'

, traverseLine
, findStart, findStartVertex, findStartDart
, follow
) where
, traverseLine
, findStart, findStartVertex, findStartDart
, follow
) where


import Geometry.Arrangement.Internal
80 changes: 77 additions & 3 deletions hgeometry/src/Geometry/PlanarSubdivision.hs
Original file line number Diff line number Diff line change
Expand Up @@ -10,9 +10,83 @@
--
--------------------------------------------------------------------------------
module Geometry.PlanarSubdivision
( module Geometry.PlanarSubdivision.Basic
( -- $setup
PlanarSubdivision

, Component, ComponentId

-- * Constructing Planar Subdivisions
, fromSimplePolygon
, fromConnectedSegments
, fromPlaneGraph, fromPlaneGraph'
, fromPolygons, fromPolygons'
, fromPolygon

-- * Quering the Planar Subdivision
, numComponents, numVertices
, numEdges, numFaces, numDarts
, dual

, components, component
, vertices', vertices
, edges', edges
, faces', internalFaces', faces, internalFaces
, darts'

-- * Incidences and Adjacencies
, headOf, tailOf, twin, endPoints

, incidentEdges, incomingEdges, outgoingEdges
, nextIncidentEdge, prevIncidentEdge
, nextIncidentEdgeFrom, prevIncidentEdgeFrom
, neighboursOf

, leftFace, rightFace
, outerBoundaryDarts, boundaryVertices, holesOf
, outerFaceId
, boundary'

, Incident (incidences)
, common, commonVertices, commonDarts, commonFaces

-- * Data
, locationOf
, HasDataOf(..)

, endPointsOf, endPointData

, faceDataOf

, traverseVertices, traverseDarts, traverseFaces
, mapVertices, mapDarts, mapFaces

-- * Obtaining a Geometric Representation
, edgeSegment, edgeSegments
, faceBoundary
, internalFacePolygon, internalFacePolygons
, outerFacePolygon, outerFacePolygon'
, facePolygons

-- * IO

-- * ReExports
, VertexId', FaceId'
, VertexId(..), FaceId(..), Dart, World(..)
, VertexData(VertexData), PG.vData, PG.location
, PlanarGraph
, PlaneGraph

-- * Helper; dealing with the Raw types
, PolygonFaceData(..)
, FaceData(FaceData), holes, fData
, Wrap
, rawVertexData, rawDartData, rawFaceData
, vertexData, dartData, faceData
, dataVal
, dartMapping, Raw(..)
, asLocalD, asLocalV, asLocalF


) where

-- import Algorithms.Geometry.PolygonTriangulation.Triangulate
Expand All @@ -22,9 +96,9 @@ import qualified Data.Vector as V
import qualified Data.List.NonEmpty as NonEmpty
import Geometry.PlanarSubdivision.Basic
import Geometry.PlanarSubdivision.Merge
import Geometry.PlanarSubdivision.TreeRep
import Geometry.PlanarSubdivision.TreeRep()
import Geometry.Polygon

import qualified Data.PlaneGraph as PG

-- import Geometry.Point
-- import qualified Data.List.NonEmpty as NonEmpty
Expand Down

0 comments on commit 8bebc3d

Please sign in to comment.