Skip to content

Commit

Permalink
Update to the new Hiraffe (#259)
Browse files Browse the repository at this point in the history
* updating to the new hiraffe

* make it compile

* more fixes ( + slowly getting rid of hsYAML)

* removing dependency on HsYAML for licencing reasons

* fix the examples
  • Loading branch information
noinia authored Dec 22, 2024
1 parent 2026903 commit e3c363e
Show file tree
Hide file tree
Showing 21 changed files with 376 additions and 77 deletions.
2 changes: 1 addition & 1 deletion hgeometry-examples/draw/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -16,7 +16,7 @@ import Test.QuickCheck

type R = RealNumber 5

renderGraph :: PlaneGraph QuickCheckWorld (Point 2 R) () () -> IpePage R
renderGraph :: CPlaneGraph QuickCheckWorld (Point 2 R) () () -> IpePage R
renderGraph gr = fromContent $
concat [ [ iO $ defIO p | p <- gr^..vertices ]
, [ iO $ defIO seg | seg <- gr^..edgeSegments ]
Expand Down
2 changes: 1 addition & 1 deletion hgeometry-examples/skia/GeometryStore.hs
Original file line number Diff line number Diff line change
Expand Up @@ -39,7 +39,7 @@ data Geom = G_Point (Point 2 R :+ Attributes (Point 2 R))

data MyWorld

type PlaneGraph' r = PlaneGraph MyWorld (Point 2 r) PolygonEdgeType PolygonFaceData
type PlaneGraph' r = CPlaneGraph MyWorld (Point 2 r) PolygonEdgeType PolygonFaceData

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

Expand Down
2 changes: 1 addition & 1 deletion hgeometry-examples/skia/Model.hs
Original file line number Diff line number Diff line change
Expand Up @@ -78,7 +78,7 @@ currentStatus m1 m2
-- in planeGraphs
data MyWorld

type PlaneGraph' r = PlaneGraph MyWorld (Point 2 r) PolygonEdgeType PolygonFaceData
type PlaneGraph' r = CPlaneGraph MyWorld (Point 2 r) PolygonEdgeType PolygonFaceData

--------------------------------------------------------------------------------
-- * Data Type representing all our modal data
Expand Down
2 changes: 1 addition & 1 deletion hgeometry-examples/triangulateWorld/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -79,7 +79,7 @@ mainWith (Options inFile outFile) = do
intersections' :: Set.Set (Point 2 R)
intersections' = foldMap computeIntersections polies

subdivs :: [PlaneGraph PX (Point 2 R) _ _]
subdivs :: [CPlaneGraph PX (Point 2 R) _ _]
subdivs = map (\(pg :+ _) -> triangulate pg) polies'

triangles' :: [SimplePolygon (Point 2 R :+ _)]
Expand Down
6 changes: 4 additions & 2 deletions hgeometry/hgeometry.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -75,7 +75,7 @@ common all-setup
, file-io >= 0.1 && < 1
, indexed-traversable >= 0.1.3 && < 1
, vector-builder >= 0.3.8 && < 1
, HsYAML >= 0.2 && < 1
-- , HsYAML >= 0.2 && < 1
, semialign >= 1.3 && < 1.4
, these >= 1.0.1 && < 1.3
, subcategories >= 0.2 && < 0.3
Expand Down Expand Up @@ -356,6 +356,7 @@ library

HGeometry.PlaneGraph
HGeometry.PlaneGraph.Class
HGeometry.PlaneGraph.Connected

HGeometry.Polygon
HGeometry.Polygon.Class
Expand Down Expand Up @@ -446,7 +447,8 @@ library
HGeometry.Polygon.Convex.MinkowskiSum
HGeometry.Polygon.Triangulation.Types

HGeometry.PlaneGraph.Type
-- HGeometry.PlaneGraph.Type
HGeometry.PlaneGraph.Connected.Type

HGeometry.LineSegment.Intersection.Types

Expand Down
5 changes: 3 additions & 2 deletions hgeometry/point/src/HGeometry/Point/PointF.hs
Original file line number Diff line number Diff line change
Expand Up @@ -24,7 +24,7 @@ import Data.Proxy
import qualified Data.Vector.Generic as G
import qualified Data.Vector.Generic.Mutable as GM
import qualified Data.Vector.Unboxed as U
import Data.YAML
-- import Data.YAML
import GHC.Generics (Generic)
import GHC.TypeLits
import HGeometry.Point.Class
Expand All @@ -38,7 +38,8 @@ import Text.Read (Read (..), readListPrecDefault)
-- | A Point wraps a vector
newtype PointF v = Point { toVec :: v }
deriving stock (Generic)
deriving newtype ( Eq, Ord, Random, NFData, Bounded, Enum, FromYAML, ToYAML
deriving newtype ( Eq, Ord, Random, NFData, Bounded, Enum
-- , FromYAML, ToYAML
, ToJSON, FromJSON
)
-- don't derive functor, or so here. since that will be confusing.
Expand Down
8 changes: 4 additions & 4 deletions hgeometry/src-quickcheck/HGeometry/PlaneGraph/Instances.hs
Original file line number Diff line number Diff line change
Expand Up @@ -57,7 +57,7 @@ data QuickCheckWorld
instance ( Arbitrary r
, Ord r, Fractional r
, Show r
) => Arbitrary (PlaneGraph QuickCheckWorld (Point 2 r) () ()) where
) => Arbitrary (CPlaneGraph QuickCheckWorld (Point 2 r) () ()) where
arbitrary = arbitraryPlaneGraph Proxy

-- general strategy:
Expand All @@ -73,7 +73,7 @@ arbitraryPlaneGraph :: forall proxy s r.
( Ord r, Fractional r, Arbitrary r
, Show r
)
=> proxy s -> Gen (PlaneGraph s (Point 2 r) () ())
=> proxy s -> Gen (CPlaneGraph s (Point 2 r) () ())
arbitraryPlaneGraph proxy = do
n <- scale (*2) arbitrary
(pts :: NonEmpty (Point 2 r)) <- genNDistinct (max 10 n) arbitrary
Expand Down Expand Up @@ -137,8 +137,8 @@ witherGraphTo vs (Graph gr) = Graph $ fmap removeEdges m
-- \(O(n\log n)\)
toPlaneGraph :: (Ord r, Foldable1 f)
=> proxy s
-> GGraph f (Point 2 r) v e -> PlaneGraph s (Point 2 r) () ()
toPlaneGraph _ (Graph m) = PlaneGraph $ (planarGraph theDarts)&vertexData .~ vtxData
-> GGraph f (Point 2 r) v e -> CPlaneGraph s (Point 2 r) () ()
toPlaneGraph _ (Graph m) = CPlaneGraph $ (planarGraph theDarts)&vertexData .~ vtxData
where
vtxData = Vector.fromNonEmptyN1 (length m) (NEMap.keys m)

Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -27,7 +27,7 @@ import HGeometry.HyperPlane.Class
import HGeometry.HyperPlane.NonVertical
import HGeometry.Plane.LowerEnvelope.Connected.MonoidalMap
import HGeometry.Plane.LowerEnvelope.Connected.Type
import HGeometry.PlaneGraph.Type (E(..))
import HGeometry.PlaneGraph.Connected.Type (E(..))
import HGeometry.Point
import HGeometry.Vector
import Hiraffe.AdjacencyListRep.Map
Expand Down
6 changes: 3 additions & 3 deletions hgeometry/src/HGeometry/PlaneGraph.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
--------------------------------------------------------------------------------
-- |
-- Module : HGeometry.PlaneGraph
-- Module : HGeometry.PlaneGraph.Connected
-- Copyright : (C) Frank Staals
-- License : see the LICENSE file
-- Maintainer : Frank Staals
Expand All @@ -12,13 +12,13 @@ module HGeometry.PlaneGraph
( module Hiraffe.Graph.Class
, module HGeometry.PlaneGraph.Class
, module Hiraffe.PlanarGraph.Class
, PlaneGraph(..)
, CPlaneGraph(..)
, fromAdjacencyRep
, fromConnectedSegments
) where

import HGeometry.PlaneGraph.Class
import HGeometry.PlaneGraph.Type
import HGeometry.PlaneGraph.Connected
import Hiraffe.Graph.Class
import Hiraffe.PlanarGraph.Class

Expand Down
2 changes: 2 additions & 0 deletions hgeometry/src/HGeometry/PlaneGraph/Class.hs
Original file line number Diff line number Diff line change
Expand Up @@ -50,6 +50,8 @@ class ( PlanarGraph_ planeGraph
, vertex ~ Vertex planeGraph
, Point_ vertex 2 (NumType vertex)
, NumType vertex ~ NumType planeGraph
-- , HasVertices graph graph
, HasEdges planeGraph planeGraph
) => PlaneGraph_ planeGraph vertex | planeGraph -> vertex where

{-# MINIMAL fromEmbedding #-}
Expand Down
26 changes: 26 additions & 0 deletions hgeometry/src/HGeometry/PlaneGraph/Connected.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,26 @@
--------------------------------------------------------------------------------
-- |
-- Module : HGeometry.PlaneGraph.Connected
-- Copyright : (C) Frank Staals
-- License : see the LICENSE file
-- Maintainer : Frank Staals
--
-- Plane Graphs, i.e. embedded planar graphs.
--
--------------------------------------------------------------------------------
module HGeometry.PlaneGraph.Connected
( module Hiraffe.Graph.Class
, module HGeometry.PlaneGraph.Class
, module Hiraffe.PlanarGraph.Class
, CPlaneGraph(..)
, fromAdjacencyRep
, fromConnectedSegments
) where

import HGeometry.PlaneGraph.Class
import HGeometry.PlaneGraph.Connected.Type
import Hiraffe.Graph.Class
import Hiraffe.PlanarGraph.Class


--------------------------------------------------------------------------------
Loading

0 comments on commit e3c363e

Please sign in to comment.