hgeometry-0.14: Geometric Algorithms, Data structures, and Data types.
Copyright(C) Frank Staals
Licensesee the LICENSE file
MaintainerFrank Staals
Safe HaskellNone
LanguageHaskell2010

Data.PlaneGraph

Description

Data type for planar graphs embedded in \(\mathbb{R}^2\). For functions that export faces and edges etc, we assume the graph has a (planar) straight line embedding.

Synopsis

Documentation

>>> import Data.Proxy
>>> import Data.PlaneGraph.AdjRep(Gr(Gr),Face(Face),Vtx(Vtx))
>>> import Data.PlaneGraph.IO(fromAdjRep)
>>> import Data.PlanarGraph.Dart(Dart(..),Arc(..))
>>> :{
let dart i s = Dart (Arc i) (read s)
    small :: Gr (Vtx Int String Int) (Face String)
    small = Gr [ Vtx 0 (Point2 0 0) [ (2,"0->2")
                                    , (1,"0->1")
                                    , (3,"0->3")
                                    ] 0
               , Vtx 1 (Point2 2 2) [ (0,"1->0")
                                    , (2,"1->2")
                                    , (3,"1->3")
                                    ] 1
               , Vtx 2 (Point2 2 0) [ (0,"2->0")
                                    , (1,"2->1")
                                    ] 2
               , Vtx 3 (Point2 (-1) 4) [ (0,"3->0")
                                       , (1,"3->1")
                                       ] 3
               ]
               [ Face (2,1) "OuterFace"
               , Face (0,1) "A"
               , Face (1,0) "B"
               ]
    smallG = fromAdjRep (Proxy :: Proxy ()) small
:}

This represents the following graph. Note that the graph is undirected, the arrows are just to indicate what the Positive direction of the darts is.

Here is also a slightly larger example graph:

>>> import Data.RealNumber.Rational
>>> data MyWorld
>>> :{
let myPlaneGraph :: PlaneGraph MyWorld Int () String (RealNumber 5)
    myPlaneGraph = fromAdjRep (Proxy @MyWorld) myPlaneGraphAdjrep
    myPlaneGraphAdjrep :: Gr (Vtx Int () (RealNumber 5)) (Face String)
    myPlaneGraphAdjrep = Gr [ vtx 0 (Point2 0   0   ) [e 9, e 5, e 1, e 2]
                            , vtx 1 (Point2 4   4   ) [e 0, e 5, e 12]
                            , vtx 2 (Point2 3   7   ) [e 0, e 3]
                            , vtx 3 (Point2 0   5   ) [e 4, e 2]
                            , vtx 4 (Point2 3   8   ) [e 3, e 13]
                            , vtx 5 (Point2 8   1   ) [e 0, e 6, e 8, e 1]
                            , vtx 6 (Point2 6   (-1)) [e 5, e 9]
                            , vtx 7 (Point2 9   (-1)) [e 8, e 11]
                            , vtx 8 (Point2 12  1   ) [e 7, e 12, e 5]
                            , vtx 9 (Point2 8   (-5)) [e 0, e 10, e 6]
                            , vtx 10 (Point2 12 (-3)) [e 9, e 11]
                            , vtx 11 (Point2 14 (-1)) [e 10, e 7]
                            , vtx 12 (Point2 10 4   ) [e 1, e 8, e 13, e 14]
                            , vtx 13 (Point2 9  6   ) [e 4, e 14, e 12]
                            , vtx 14 (Point2 8  5   ) [e 13, e 12]
                            ]
                            [ Face (0,9) "OuterFace"
                            , Face (0,5) "A"
                            , Face (0,1) "B"
                            , Face (0,2) "C"
                            , Face (14,13) "D"
                            , Face (1,12) "E"
                            , Face (5,8) "F"
                            ]
      where
        e i = (i,())
        vtx i p es = Vtx i p es i
:}

newtype PlaneGraph s v e f r Source #

Embedded, *connected*, planar graph

Constructors

PlaneGraph (PlanarGraph s Primal (VertexData r v) e f) 

Instances

Instances details
Functor (PlaneGraph s v e f) Source # 
Instance details

Defined in Data.PlaneGraph.Core

Methods

fmap :: (a -> b) -> PlaneGraph s v e f a -> PlaneGraph s v e f b #

(<$) :: a -> PlaneGraph s v e f b -> PlaneGraph s v e f a #

(Eq r, Eq v, Eq e, Eq f) => Eq (PlaneGraph s v e f r) Source # 
Instance details

Defined in Data.PlaneGraph.Core

Methods

(==) :: PlaneGraph s v e f r -> PlaneGraph s v e f r -> Bool #

(/=) :: PlaneGraph s v e f r -> PlaneGraph s v e f r -> Bool #

(Show r, Show v, Show e, Show f) => Show (PlaneGraph s v e f r) Source # 
Instance details

Defined in Data.PlaneGraph.Core

Methods

showsPrec :: Int -> PlaneGraph s v e f r -> ShowS #

show :: PlaneGraph s v e f r -> String #

showList :: [PlaneGraph s v e f r] -> ShowS #

Generic (PlaneGraph s v e f r) Source # 
Instance details

Defined in Data.PlaneGraph.Core

Associated Types

type Rep (PlaneGraph s v e f r) :: Type -> Type #

Methods

from :: PlaneGraph s v e f r -> Rep (PlaneGraph s v e f r) x #

to :: Rep (PlaneGraph s v e f r) x -> PlaneGraph s v e f r #

(ToJSON v, ToJSON e, ToJSON f, ToJSON r) => ToJSON (PlaneGraph s v e f r) Source # 
Instance details

Defined in Data.PlaneGraph.IO

Methods

toJSON :: PlaneGraph s v e f r -> Value #

toEncoding :: PlaneGraph s v e f r -> Encoding #

toJSONList :: [PlaneGraph s v e f r] -> Value #

toEncodingList :: [PlaneGraph s v e f r] -> Encoding #

(FromJSON v, FromJSON e, FromJSON f, FromJSON r) => FromJSON (PlaneGraph s v e f r) Source # 
Instance details

Defined in Data.PlaneGraph.IO

Methods

parseJSON :: Value -> Parser (PlaneGraph s v e f r) #

parseJSONList :: Value -> Parser [PlaneGraph s v e f r] #

IsBoxable (PlaneGraph s v e f r) Source # 
Instance details

Defined in Data.PlaneGraph.Core

Methods

boundingBox :: PlaneGraph s v e f r -> Box (Dimension (PlaneGraph s v e f r)) () (NumType (PlaneGraph s v e f r)) Source #

HasDataOf (PlaneGraph s v e f r) (FaceId' s) Source # 
Instance details

Defined in Data.PlaneGraph.Core

Associated Types

type DataOf (PlaneGraph s v e f r) (FaceId' s) #

Methods

dataOf :: FaceId' s -> Lens' (PlaneGraph s v e f r) (DataOf (PlaneGraph s v e f r) (FaceId' s)) #

HasDataOf (PlaneGraph s v e f r) (Dart s) Source # 
Instance details

Defined in Data.PlaneGraph.Core

Associated Types

type DataOf (PlaneGraph s v e f r) (Dart s) #

Methods

dataOf :: Dart s -> Lens' (PlaneGraph s v e f r) (DataOf (PlaneGraph s v e f r) (Dart s)) #

HasDataOf (PlaneGraph s v e f r) (VertexId' s) Source # 
Instance details

Defined in Data.PlaneGraph.Core

Associated Types

type DataOf (PlaneGraph s v e f r) (VertexId' s) #

Methods

dataOf :: VertexId' s -> Lens' (PlaneGraph s v e f r) (DataOf (PlaneGraph s v e f r) (VertexId' s)) #

type Rep (PlaneGraph s v e f r) Source # 
Instance details

Defined in Data.PlaneGraph.Core

type Rep (PlaneGraph s v e f r) = D1 ('MetaData "PlaneGraph" "Data.PlaneGraph.Core" "hgeometry-0.14-BBhGh1sNn85H5mfsjBn14s" 'True) (C1 ('MetaCons "PlaneGraph" 'PrefixI 'True) (S1 ('MetaSel ('Just "_graph") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PlanarGraph s 'Primal (VertexData r v) e f))))
type NumType (PlaneGraph s v e f r) Source # 
Instance details

Defined in Data.PlaneGraph.Core

type NumType (PlaneGraph s v e f r) = r
type Dimension (PlaneGraph s v e f r) Source # 
Instance details

Defined in Data.PlaneGraph.Core

type Dimension (PlaneGraph s v e f r) = 2
type DataOf (PlaneGraph s v e f r) (FaceId' s) Source # 
Instance details

Defined in Data.PlaneGraph.Core

type DataOf (PlaneGraph s v e f r) (FaceId' s) = f
type DataOf (PlaneGraph s v e f r) (Dart s) Source # 
Instance details

Defined in Data.PlaneGraph.Core

type DataOf (PlaneGraph s v e f r) (Dart s) = e
type DataOf (PlaneGraph s v e f r) (VertexId' s) Source # 
Instance details

Defined in Data.PlaneGraph.Core

type DataOf (PlaneGraph s v e f r) (VertexId' s) = v

graph :: forall k (s :: k) v e f r k (s :: k) v e f r. Iso (PlaneGraph (s :: k) v e f r) (PlaneGraph (s :: k) v e f r) (PlanarGraph s 'Primal (VertexData r v) e f) (PlanarGraph s 'Primal (VertexData r v) e f) Source #

data PlanarGraph (s :: k) (w :: World) v e f #

A *connected* Planar graph with bidirected edges. I.e. the edges (darts) are directed, however, for every directed edge, the edge in the oposite direction is also in the graph.

The types v, e, and f are the are the types of the data associated with the vertices, edges, and faces, respectively.

The orbits in the embedding are assumed to be in counterclockwise order. Therefore, every dart directly bounds the face to its right.

Instances

Instances details
(Eq v, Eq e, Eq f) => Eq (PlanarGraph s w v e f) 
Instance details

Defined in Data.PlanarGraph.Core

Methods

(==) :: PlanarGraph s w v e f -> PlanarGraph s w v e f -> Bool #

(/=) :: PlanarGraph s w v e f -> PlanarGraph s w v e f -> Bool #

(Show v, Show e, Show f) => Show (PlanarGraph s w v e f) 
Instance details

Defined in Data.PlanarGraph.Core

Methods

showsPrec :: Int -> PlanarGraph s w v e f -> ShowS #

show :: PlanarGraph s w v e f -> String #

showList :: [PlanarGraph s w v e f] -> ShowS #

Generic (PlanarGraph s w v e f) 
Instance details

Defined in Data.PlanarGraph.Core

Associated Types

type Rep (PlanarGraph s w v e f) :: Type -> Type #

Methods

from :: PlanarGraph s w v e f -> Rep (PlanarGraph s w v e f) x #

to :: Rep (PlanarGraph s w v e f) x -> PlanarGraph s w v e f #

HasDataOf (PlanarGraph s w v e f) (Dart s) 
Instance details

Defined in Data.PlanarGraph.Core

Associated Types

type DataOf (PlanarGraph s w v e f) (Dart s) #

Methods

dataOf :: Dart s -> Lens' (PlanarGraph s w v e f) (DataOf (PlanarGraph s w v e f) (Dart s)) #

HasDataOf (PlanarGraph s w v e f) (VertexId s w) 
Instance details

Defined in Data.PlanarGraph.Core

Associated Types

type DataOf (PlanarGraph s w v e f) (VertexId s w) #

Methods

dataOf :: VertexId s w -> Lens' (PlanarGraph s w v e f) (DataOf (PlanarGraph s w v e f) (VertexId s w)) #

HasDataOf (PlanarGraph s w v e f) (FaceId s w) 
Instance details

Defined in Data.PlanarGraph.Core

Associated Types

type DataOf (PlanarGraph s w v e f) (FaceId s w) #

Methods

dataOf :: FaceId s w -> Lens' (PlanarGraph s w v e f) (DataOf (PlanarGraph s w v e f) (FaceId s w)) #

type Rep (PlanarGraph s w v e f) 
Instance details

Defined in Data.PlanarGraph.Core

type Rep (PlanarGraph s w v e f) = D1 ('MetaData "PlanarGraph" "Data.PlanarGraph.Core" "hgeometry-combinatorial-0.14-4eKKoxfw4Iy23UosEmuxsr" 'False) (C1 ('MetaCons "PlanarGraph" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_embedding") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Permutation (Dart s))) :*: S1 ('MetaSel ('Just "_vertexData") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Vector v))) :*: (S1 ('MetaSel ('Just "_rawDartData") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Vector e)) :*: (S1 ('MetaSel ('Just "_faceData") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Vector f)) :*: S1 ('MetaSel ('Just "_dual") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PlanarGraph s (DualOf w) f e v))))))
type DataOf (PlanarGraph s w v e f) (Dart s) 
Instance details

Defined in Data.PlanarGraph.Core

type DataOf (PlanarGraph s w v e f) (Dart s) = e
type DataOf (PlanarGraph s w v e f) (VertexId s w) 
Instance details

Defined in Data.PlanarGraph.Core

type DataOf (PlanarGraph s w v e f) (VertexId s w) = v
type DataOf (PlanarGraph s w v e f) (FaceId s w) 
Instance details

Defined in Data.PlanarGraph.Core

type DataOf (PlanarGraph s w v e f) (FaceId s w) = f

data VertexData r v Source #

Note that the functor instance is in v

Constructors

VertexData !(Point 2 r) !v 

Instances

Instances details
Bifunctor VertexData Source # 
Instance details

Defined in Data.PlaneGraph.Core

Methods

bimap :: (a -> b) -> (c -> d) -> VertexData a c -> VertexData b d #

first :: (a -> b) -> VertexData a c -> VertexData b c #

second :: (b -> c) -> VertexData a b -> VertexData a c #

Functor (VertexData r) Source # 
Instance details

Defined in Data.PlaneGraph.Core

Methods

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

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

Foldable (VertexData r) Source # 
Instance details

Defined in Data.PlaneGraph.Core

Methods

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

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

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

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

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

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

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

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

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

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

null :: VertexData r a -> Bool #

length :: VertexData r a -> Int #

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

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

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

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

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

Traversable (VertexData r) Source # 
Instance details

Defined in Data.PlaneGraph.Core

Methods

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

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

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

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

(Eq r, Eq v) => Eq (VertexData r v) Source # 
Instance details

Defined in Data.PlaneGraph.Core

Methods

(==) :: VertexData r v -> VertexData r v -> Bool #

(/=) :: VertexData r v -> VertexData r v -> Bool #

(Ord r, Ord v) => Ord (VertexData r v) Source # 
Instance details

Defined in Data.PlaneGraph.Core

Methods

compare :: VertexData r v -> VertexData r v -> Ordering #

(<) :: VertexData r v -> VertexData r v -> Bool #

(<=) :: VertexData r v -> VertexData r v -> Bool #

(>) :: VertexData r v -> VertexData r v -> Bool #

(>=) :: VertexData r v -> VertexData r v -> Bool #

max :: VertexData r v -> VertexData r v -> VertexData r v #

min :: VertexData r v -> VertexData r v -> VertexData r v #

(Show r, Show v) => Show (VertexData r v) Source # 
Instance details

Defined in Data.PlaneGraph.Core

Methods

showsPrec :: Int -> VertexData r v -> ShowS #

show :: VertexData r v -> String #

showList :: [VertexData r v] -> ShowS #

Generic (VertexData r v) Source # 
Instance details

Defined in Data.PlaneGraph.Core

Associated Types

type Rep (VertexData r v) :: Type -> Type #

Methods

from :: VertexData r v -> Rep (VertexData r v) x #

to :: Rep (VertexData r v) x -> VertexData r v #

(ToJSON r, ToJSON v) => ToJSON (VertexData r v) Source # 
Instance details

Defined in Data.PlaneGraph.Core

(FromJSON r, FromJSON v) => FromJSON (VertexData r v) Source # 
Instance details

Defined in Data.PlaneGraph.Core

type Rep (VertexData r v) Source # 
Instance details

Defined in Data.PlaneGraph.Core

type Rep (VertexData r v) = D1 ('MetaData "VertexData" "Data.PlaneGraph.Core" "hgeometry-0.14-BBhGh1sNn85H5mfsjBn14s" 'False) (C1 ('MetaCons "VertexData" 'PrefixI 'True) (S1 ('MetaSel ('Just "_location") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Point 2 r)) :*: S1 ('MetaSel ('Just "_vData") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 v)))

vData :: forall r v v. Lens (VertexData r v) (VertexData r v) v v Source #

location :: forall r v r. Lens (VertexData r v) (VertexData r v) (Point 2 r) (Point 2 r) Source #

vtxDataToExt :: VertexData r v -> Point 2 r :+ v Source #

Convert to an Ext

fromSimplePolygon Source #

Arguments

:: forall s p r f. SimplePolygon p r 
-> f

data inside

-> f

data outside the polygon

-> PlaneGraph s p () f r 

Construct a plane graph from a simple polygon. It is assumed that the polygon is given in counterclockwise order.

the interior of the polygon will have faceId 0

pre: the input polygon is given in counterclockwise order running time: \(O(n)\).

fromConnectedSegments :: forall s p r e f. (Foldable f, Ord r, Num r) => f (LineSegment 2 p r :+ e) -> PlaneGraph s (NonEmpty p) e () r Source #

Constructs a connected plane graph

pre: The segments form a single connected component

running time: \(O(n\log n)\)

toAdjRep :: PlaneGraph s v e f r -> Gr (Vtx v e r) (Face f) Source #

Transforms the plane graph into adjacency lists. For every vertex, the adjacent vertices are given in counter clockwise order.

See toAdjacencyLists for notes on how we handle self-loops.

running time: \(O(n)\)

fromAdjRep :: forall s v e f r. Gr (Vtx v e r) (Face f) -> PlaneGraph s v e f r Source #

Given the AdjacencyList representation of a plane graph, construct the plane graph representing it. All the adjacencylists should be in counter clockwise order.

running time: \(O(n)\)

numVertices :: PlaneGraph s v e f r -> Int Source #

Get the number of vertices

>>> numVertices smallG
4
>>> numVertices myPlaneGraph
15

numEdges :: PlaneGraph s v e f r -> Int Source #

Get the number of Edges

>>> numEdges smallG
5

numFaces :: PlaneGraph s v e f r -> Int Source #

Get the number of faces

>>> numFaces smallG
3
>>> numFaces myPlaneGraph
7

numDarts :: PlaneGraph s v e f r -> Int Source #

Get the number of Darts

>>> numDarts smallG
10

dual :: forall k (s :: k) (w :: World) v e f. Getter (PlanarGraph s w v e f) (PlanarGraph s (DualOf w) f e v) #

Get the dual graph of this graph.

vertices' :: PlaneGraph s v e f r -> Vector (VertexId' s) Source #

Enumerate all vertices

>>> vertices' smallG
[VertexId 0,VertexId 1,VertexId 2,VertexId 3]

vertices :: PlaneGraph s v e f r -> Vector (VertexId' s, VertexData r v) Source #

Enumerate all vertices, together with their vertex data

>>> mapM_ print $ vertices smallG
(VertexId 0,VertexData {_location = Point2 0 0, _vData = 0})
(VertexId 1,VertexData {_location = Point2 2 2, _vData = 1})
(VertexId 2,VertexData {_location = Point2 2 0, _vData = 2})
(VertexId 3,VertexData {_location = Point2 (-1) 4, _vData = 3})

edges' :: PlaneGraph s v e f r -> Vector (Dart s) Source #

Enumerate all edges. We report only the Positive darts

edges :: PlaneGraph s v e f r -> Vector (Dart s, e) Source #

Enumerate all edges with their edge data. We report only the Positive darts.

>>> mapM_ print $ edges smallG
(Dart (Arc 0) +1,"0->2")
(Dart (Arc 1) +1,"0->1")
(Dart (Arc 2) +1,"0->3")
(Dart (Arc 4) +1,"1->2")
(Dart (Arc 3) +1,"1->3")

faces' :: PlaneGraph s v e f r -> Vector (FaceId' s) Source #

Enumerate all faces in the plane graph

faces :: PlaneGraph s v e f r -> Vector (FaceId' s, f) Source #

All faces with their face data.

>>> mapM_ print $ faces smallG
(FaceId 0,"OuterFace")
(FaceId 1,"A")
(FaceId 2,"B")
>>> mapM_ print $ faces myPlaneGraph
(FaceId 0,"OuterFace")
(FaceId 1,"A")
(FaceId 2,"B")
(FaceId 3,"C")
(FaceId 4,"E")
(FaceId 5,"F")
(FaceId 6,"D")

internalFaces :: (Ord r, Num r) => PlaneGraph s v e f r -> Vector (FaceId' s, f) Source #

Reports all internal faces. running time: \(O(n)\)

faces'' :: (Ord r, Num r) => PlaneGraph s v e f r -> ((FaceId' s, f), Vector (FaceId' s, f)) Source #

Reports the outerface and all internal faces separately. running time: \(O(n)\)

darts' :: PlaneGraph s v e f r -> Vector (Dart s) Source #

Enumerate all darts

darts :: PlaneGraph s v e f r -> Vector (Dart s, e) Source #

Get all darts together with their data

traverseVertices :: Applicative m => (VertexId' s -> v -> m v') -> PlaneGraph s v e f r -> m (PlaneGraph s v' e f r) Source #

Traverse the vertices

(^.vertexData) $ traverseVertices (i x -> Just (i,x)) smallG Just [(VertexId 0,0),(VertexId 1,1),(VertexId 2,2),(VertexId 3,3)] >>> traverseVertices (i x -> print (i,x)) smallG >> pure () (VertexId 0,0) (VertexId 1,1) (VertexId 2,2) (VertexId 3,3)

traverseDarts :: Applicative m => (Dart s -> e -> m e') -> PlaneGraph s v e f r -> m (PlaneGraph s v e' f r) Source #

Traverses the darts

>>> traverseDarts (\d x -> print (d,x)) smallG >> pure ()
(Dart (Arc 0) +1,"0->2")
(Dart (Arc 0) -1,"2->0")
(Dart (Arc 1) +1,"0->1")
(Dart (Arc 1) -1,"1->0")
(Dart (Arc 2) +1,"0->3")
(Dart (Arc 2) -1,"3->0")
(Dart (Arc 3) +1,"1->3")
(Dart (Arc 3) -1,"3->1")
(Dart (Arc 4) +1,"1->2")
(Dart (Arc 4) -1,"2->1")

traverseFaces :: Applicative m => (FaceId' s -> f -> m f') -> PlaneGraph s v e f r -> m (PlaneGraph s v e f' r) Source #

Traverses the faces

>>> traverseFaces (\i x -> print (i,x)) smallG >> pure ()
(FaceId 0,"OuterFace")
(FaceId 1,"A")
(FaceId 2,"B")

headOf :: Dart s -> PlaneGraph s v e f r -> VertexId' s Source #

The vertex this dart is heading in to

running time: \(O(1)\)

>>> headOf (dart 0 "+1") smallG
VertexId 2

tailOf :: Dart s -> PlaneGraph s v e f r -> VertexId' s Source #

The tail of a dart, i.e. the vertex this dart is leaving from

running time: \(O(1)\)

>>> tailOf (dart 0 "+1") smallG
VertexId 0

twin :: forall k (s :: k). Dart s -> Dart s #

Get the twin of this dart (edge)

>>> twin (dart 0 "+1")
Dart (Arc 0) -1
>>> twin (dart 0 "-1")
Dart (Arc 0) +1

endPoints :: Dart s -> PlaneGraph s v e f r -> (VertexId' s, VertexId' s) Source #

endPoints d g = (tailOf d g, headOf d g)

running time: \(O(1)\)

>>> endPoints (dart 0 "+1") smallG
(VertexId 0,VertexId 2)

incidentEdges :: VertexId' s -> PlaneGraph s v e f r -> Vector (Dart s) Source #

All edges incident to vertex v, in counterclockwise order around v.

running time: \(O(k)\), where \(k\) is the output size

>>> incidentEdges (VertexId 1) smallG
[Dart (Arc 1) -1,Dart (Arc 4) +1,Dart (Arc 3) +1]
>>> mapM_ print $ incidentEdges (VertexId 5) myPlaneGraph
Dart (Arc 1) -1
Dart (Arc 7) +1
Dart (Arc 10) +1
Dart (Arc 4) -1

incomingEdges :: VertexId' s -> PlaneGraph s v e f r -> Vector (Dart s) Source #

All edges incident to vertex v in incoming direction (i.e. pointing into v) in counterclockwise order around v.

running time: \(O(k)\), where (k) is the total number of incident edges of v

>>> incomingEdges (VertexId 1) smallG
[Dart (Arc 1) +1,Dart (Arc 4) -1,Dart (Arc 3) -1]

outgoingEdges :: VertexId' s -> PlaneGraph s v e f r -> Vector (Dart s) Source #

All edges incident to vertex v in outgoing direction (i.e. pointing out of v) in counterclockwise order around v.

running time: \(O(k)\), where (k) is the total number of incident edges of v

>>> outgoingEdges (VertexId 1) smallG
[Dart (Arc 1) -1,Dart (Arc 4) +1,Dart (Arc 3) +1]

neighboursOf :: VertexId' s -> PlaneGraph s v e f r -> Vector (VertexId' s) Source #

Gets the neighbours of a particular vertex, in counterclockwise order around the vertex.

running time: \(O(k)\), where \(k\) is the output size

>>> neighboursOf (VertexId 1) smallG
[VertexId 0,VertexId 2,VertexId 3]
>>> neighboursOf (VertexId 5) myPlaneGraph
[VertexId 0,VertexId 6,VertexId 8,VertexId 1]

nextIncidentEdge :: Dart s -> PlaneGraph s v e f r -> Dart s Source #

Given a dart d that points into some vertex v, report the next dart in the cyclic (counterclockwise) order around v.

running time: \(O(1)\)

>>> nextIncidentEdge (dart 1 "+1") smallG
Dart (Arc 4) +1
>>> nextIncidentEdge (dart 1 "+1") myPlaneGraph
Dart (Arc 7) +1
>>> nextIncidentEdge (dart 17 "-1") myPlaneGraph
Dart (Arc 15) -1

prevIncidentEdge :: Dart s -> PlaneGraph s v e f r -> Dart s Source #

Given a dart d that points into some vertex v, report the previous dart in the cyclic (counterclockwise) order around v.

running time: \(O(1)\)

>>> prevIncidentEdge (dart 1 "+1") smallG
Dart (Arc 3) +1
>>> prevIncidentEdge (dart 1 "+1") myPlaneGraph
Dart (Arc 4) -1
>>> prevIncidentEdge (dart 7 "-1") myPlaneGraph
Dart (Arc 1) -1

nextIncidentEdgeFrom :: Dart s -> PlaneGraph s v e f r -> Dart s Source #

Given a dart d that points away from some vertex v, report the next dart in the cyclic (counterclockwise) order around v.

running time: \(O(1)\)

>>> nextIncidentEdgeFrom (dart 1 "+1") smallG
Dart (Arc 2) +1
>>> nextIncidentEdgeFrom (dart 1 "+1") myPlaneGraph
Dart (Arc 2) +1
>>> nextIncidentEdgeFrom (dart 4 "+1") myPlaneGraph
Dart (Arc 15) +1

prevIncidentEdgeFrom :: Dart s -> PlaneGraph s v e f r -> Dart s Source #

Given a dart d that points into away from vertex v, report the previous dart in the cyclic (counterclockwise) order around v.

running time: \(O(1)\)

>>> prevIncidentEdgeFrom (dart 1 "+1") smallG
Dart (Arc 0) +1
>>> prevIncidentEdgeFrom (dart 4 "+1") myPlaneGraph
Dart (Arc 2) -1

leftFace :: Dart s -> PlaneGraph s v e f r -> FaceId' s Source #

The face to the left of the dart

running time: \(O(1)\).

>>> leftFace (dart 1 "+1") smallG
FaceId 2
>>> leftFace (dart 1 "-1") smallG
FaceId 1
>>> leftFace (dart 2 "+1") smallG
FaceId 0
>>> leftFace (dart 2 "-1") smallG
FaceId 2

rightFace :: Dart s -> PlaneGraph s v e f r -> FaceId' s Source #

The face to the right of the dart

running time: \(O(1)\).

>>> rightFace (dart 1 "+1") smallG
FaceId 1
>>> rightFace (dart 1 "-1") smallG
FaceId 2
>>> rightFace (dart 2 "+1") smallG
FaceId 2
>>> rightFace (dart 2 "-1") smallG
FaceId 0

nextEdge :: Dart s -> PlaneGraph s v e f r -> Dart s Source #

Get the next edge along the face

running time: \(O(1)\).

>>> nextEdge (dart 1 "+1") smallG
Dart (Arc 4) +1

prevEdge :: Dart s -> PlaneGraph s v e f r -> Dart s Source #

Get the previous edge along the face

running time: \(O(1)\).

>>> prevEdge (dart 1 "+1") smallG
Dart (Arc 0) -1

boundary :: FaceId' s -> PlaneGraph s v e f r -> Vector (Dart s) Source #

The darts bounding this face. The darts are reported in order along the face. This means that for internal faces the darts are reported in *clockwise* order along the boundary, whereas for the outer face the darts are reported in counter clockwise order.

running time: \(O(k)\), where \(k\) is the output size.

>>> boundary (FaceId $ VertexId 2) smallG -- around face B
[Dart (Arc 2) +1,Dart (Arc 3) -1,Dart (Arc 1) -1]
>>> boundary (FaceId $ VertexId 0) smallG -- around outer face
[Dart (Arc 0) +1,Dart (Arc 4) -1,Dart (Arc 3) +1,Dart (Arc 2) -1]

boundary' :: Dart s -> PlaneGraph s v e f r -> Vector (Dart s) Source #

Given a dart d, generates the darts bounding the face that is to the right of the given dart. The darts are reported in order along the face. This means that for internal faces the darts are reported in *clockwise* order along the boundary, whereas for the outer face the darts are reported in counter clockwise order.

running time: \(O(k)\), where \(k\) is the number of darts reported

>>> boundary' (dart 2 "+1") smallG -- around face B
[Dart (Arc 2) +1,Dart (Arc 3) -1,Dart (Arc 1) -1]
>>> boundary' (dart 0 "+1") smallG -- around outer face
[Dart (Arc 0) +1,Dart (Arc 4) -1,Dart (Arc 3) +1,Dart (Arc 2) -1]

boundaryDart :: FaceId' s -> PlaneGraph s v e f r -> Dart s Source #

Gets a dart bounding this face. I.e. a dart d such that the face lies to the right of the dart.

boundaryVertices :: FaceId' s -> PlaneGraph s v e f r -> Vector (VertexId' s) Source #

The vertices bounding this face, for internal faces in clockwise order, for the outer face in counter clockwise order.

running time: \(O(k)\), where \(k\) is the output size.

>>> boundaryVertices (FaceId $ VertexId 2) smallG -- around B
[VertexId 0,VertexId 3,VertexId 1]
>>> boundaryVertices (FaceId $ VertexId 0) smallG -- around outerface
[VertexId 0,VertexId 2,VertexId 1,VertexId 3]
>>> mapM_ print $ boundaryVertices (FaceId $ VertexId 0) myPlaneGraph
VertexId 0
VertexId 9
VertexId 10
VertexId 11
VertexId 7
VertexId 8
VertexId 12
VertexId 13
VertexId 4
VertexId 3
VertexId 2

outerFaceId :: (Ord r, Num r) => PlaneGraph s v e f r -> FaceId' s Source #

gets the id of the outer face

running time: \(O(n)\)

outerFaceDart :: (Ord r, Num r) => PlaneGraph s v e f r -> Dart s Source #

gets a dart incident to the outer face (in particular, that has the outerface on its left)

running time: \(O(n)\)

vertexDataOf :: VertexId' s -> Lens' (PlaneGraph s v e f r) (VertexData r v) Source #

Lens to access the vertex data

Note that using the setting part of this lens may be very expensive!! (O(n))

locationOf :: VertexId' s -> Lens' (PlaneGraph s v e f r) (Point 2 r) Source #

Get the location of a vertex in the plane graph

Note that the setting part of this lens may be very expensive! Moreover, use with care (as this may destroy planarity etc.)

class HasDataOf g i where #

General interface to accessing vertex data, dart data, and face data.

Associated Types

type DataOf g i #

Methods

dataOf :: i -> Lens' g (DataOf g i) #

get the data associated with the value i.

running time: \(O(1)\) to read the data, \(O(n)\) to write it.

Instances

Instances details
HasDataOf (PlanarGraph s w v e f) (Dart s) 
Instance details

Defined in Data.PlanarGraph.Core

Associated Types

type DataOf (PlanarGraph s w v e f) (Dart s) #

Methods

dataOf :: Dart s -> Lens' (PlanarGraph s w v e f) (DataOf (PlanarGraph s w v e f) (Dart s)) #

HasDataOf (PlaneGraph s v e f r) (FaceId' s) Source # 
Instance details

Defined in Data.PlaneGraph.Core

Associated Types

type DataOf (PlaneGraph s v e f r) (FaceId' s) #

Methods

dataOf :: FaceId' s -> Lens' (PlaneGraph s v e f r) (DataOf (PlaneGraph s v e f r) (FaceId' s)) #

HasDataOf (PlaneGraph s v e f r) (Dart s) Source # 
Instance details

Defined in Data.PlaneGraph.Core

Associated Types

type DataOf (PlaneGraph s v e f r) (Dart s) #

Methods

dataOf :: Dart s -> Lens' (PlaneGraph s v e f r) (DataOf (PlaneGraph s v e f r) (Dart s)) #

HasDataOf (PlaneGraph s v e f r) (VertexId' s) Source # 
Instance details

Defined in Data.PlaneGraph.Core

Associated Types

type DataOf (PlaneGraph s v e f r) (VertexId' s) #

Methods

dataOf :: VertexId' s -> Lens' (PlaneGraph s v e f r) (DataOf (PlaneGraph s v e f r) (VertexId' s)) #

HasDataOf (PlanarSubdivision s v e f r) (FaceId' s) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Basic

Associated Types

type DataOf (PlanarSubdivision s v e f r) (FaceId' s) #

Methods

dataOf :: FaceId' s -> Lens' (PlanarSubdivision s v e f r) (DataOf (PlanarSubdivision s v e f r) (FaceId' s)) #

HasDataOf (PlanarSubdivision s v e f r) (Dart s) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Basic

Associated Types

type DataOf (PlanarSubdivision s v e f r) (Dart s) #

Methods

dataOf :: Dart s -> Lens' (PlanarSubdivision s v e f r) (DataOf (PlanarSubdivision s v e f r) (Dart s)) #

HasDataOf (PlanarSubdivision s v e f r) (VertexId' s) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Basic

Associated Types

type DataOf (PlanarSubdivision s v e f r) (VertexId' s) #

Methods

dataOf :: VertexId' s -> Lens' (PlanarSubdivision s v e f r) (DataOf (PlanarSubdivision s v e f r) (VertexId' s)) #

HasDataOf (PlanarGraph s w v e f) (VertexId s w) 
Instance details

Defined in Data.PlanarGraph.Core

Associated Types

type DataOf (PlanarGraph s w v e f) (VertexId s w) #

Methods

dataOf :: VertexId s w -> Lens' (PlanarGraph s w v e f) (DataOf (PlanarGraph s w v e f) (VertexId s w)) #

HasDataOf (PlanarGraph s w v e f) (FaceId s w) 
Instance details

Defined in Data.PlanarGraph.Core

Associated Types

type DataOf (PlanarGraph s w v e f) (FaceId s w) #

Methods

dataOf :: FaceId s w -> Lens' (PlanarGraph s w v e f) (DataOf (PlanarGraph s w v e f) (FaceId s w)) #

endPointsOf :: Dart s -> Getter (PlaneGraph s v e f r) (VertexData r v, VertexData r v) Source #

Getter for the data at the endpoints of a dart

running time: \(O(1)\)

endPointData :: Dart s -> PlaneGraph s v e f r -> (VertexData r v, VertexData r v) Source #

Data corresponding to the endpoints of the dart

running time: \(O(1)\)

vertexData :: Lens (PlaneGraph s v e f r) (PlaneGraph s v' e f r) (Vector v) (Vector v') Source #

faceData :: Lens (PlaneGraph s v e f r) (PlaneGraph s v e f' r) (Vector f) (Vector f') Source #

Lens to access face data

dartData :: Lens (PlaneGraph s v e f r) (PlaneGraph s v e' f r) (Vector (Dart s, e)) (Vector (Dart s, e')) Source #

lens to access the Dart Data

rawDartData :: Lens (PlaneGraph s v e f r) (PlaneGraph s v e' f r) (Vector e) (Vector e') Source #

Lens to access the raw dart data, use at your own risk

edgeSegment :: Dart s -> PlaneGraph s v e f r -> LineSegment 2 v r :+ e Source #

Given a dart and the graph constructs the line segment representing the dart. The segment \(\overline{uv})\) is has \(u\) as its tail and \(v\) as its head.

\(O(1)\)

edgeSegments :: PlaneGraph s v e f r -> Vector (Dart s, LineSegment 2 v r :+ e) Source #

Reports all edges as line segments

>>> mapM_ print $ edgeSegments smallG
(Dart (Arc 0) +1,ClosedLineSegment (Point2 0 0 :+ 0) (Point2 2 0 :+ 2) :+ "0->2")
(Dart (Arc 1) +1,ClosedLineSegment (Point2 0 0 :+ 0) (Point2 2 2 :+ 1) :+ "0->1")
(Dart (Arc 2) +1,ClosedLineSegment (Point2 0 0 :+ 0) (Point2 (-1) 4 :+ 3) :+ "0->3")
(Dart (Arc 4) +1,ClosedLineSegment (Point2 2 2 :+ 1) (Point2 2 0 :+ 2) :+ "1->2")
(Dart (Arc 3) +1,ClosedLineSegment (Point2 2 2 :+ 1) (Point2 (-1) 4 :+ 3) :+ "1->3")
>>> mapM_ print $ edgeSegments myPlaneGraph
(Dart (Arc 0) +1,ClosedLineSegment (Point2 0 0 :+ 0) (Point2 8 (-5) :+ 9) :+ ())
(Dart (Arc 1) +1,ClosedLineSegment (Point2 0 0 :+ 0) (Point2 8 1 :+ 5) :+ ())
(Dart (Arc 2) +1,ClosedLineSegment (Point2 0 0 :+ 0) (Point2 4 4 :+ 1) :+ ())
(Dart (Arc 3) +1,ClosedLineSegment (Point2 0 0 :+ 0) (Point2 3 7 :+ 2) :+ ())
(Dart (Arc 4) +1,ClosedLineSegment (Point2 4 4 :+ 1) (Point2 8 1 :+ 5) :+ ())
(Dart (Arc 15) +1,ClosedLineSegment (Point2 4 4 :+ 1) (Point2 10 4 :+ 12) :+ ())
(Dart (Arc 5) +1,ClosedLineSegment (Point2 3 7 :+ 2) (Point2 0 5 :+ 3) :+ ())
(Dart (Arc 6) +1,ClosedLineSegment (Point2 0 5 :+ 3) (Point2 3 8 :+ 4) :+ ())
(Dart (Arc 18) +1,ClosedLineSegment (Point2 3 8 :+ 4) (Point2 9 6 :+ 13) :+ ())
(Dart (Arc 7) +1,ClosedLineSegment (Point2 8 1 :+ 5) (Point2 6 (-1) :+ 6) :+ ())
(Dart (Arc 10) +1,ClosedLineSegment (Point2 8 1 :+ 5) (Point2 12 1 :+ 8) :+ ())
(Dart (Arc 12) +1,ClosedLineSegment (Point2 6 (-1) :+ 6) (Point2 8 (-5) :+ 9) :+ ())
(Dart (Arc 8) +1,ClosedLineSegment (Point2 9 (-1) :+ 7) (Point2 12 1 :+ 8) :+ ())
(Dart (Arc 14) +1,ClosedLineSegment (Point2 9 (-1) :+ 7) (Point2 14 (-1) :+ 11) :+ ())
(Dart (Arc 9) +1,ClosedLineSegment (Point2 12 1 :+ 8) (Point2 10 4 :+ 12) :+ ())
(Dart (Arc 11) +1,ClosedLineSegment (Point2 8 (-5) :+ 9) (Point2 12 (-3) :+ 10) :+ ())
(Dart (Arc 13) +1,ClosedLineSegment (Point2 12 (-3) :+ 10) (Point2 14 (-1) :+ 11) :+ ())
(Dart (Arc 16) +1,ClosedLineSegment (Point2 10 4 :+ 12) (Point2 9 6 :+ 13) :+ ())
(Dart (Arc 17) +1,ClosedLineSegment (Point2 10 4 :+ 12) (Point2 8 5 :+ 14) :+ ())
(Dart (Arc 19) +1,ClosedLineSegment (Point2 9 6 :+ 13) (Point2 8 5 :+ 14) :+ ())

faceBoundary :: FaceId' s -> PlaneGraph s v e f r -> SimplePolygon v r :+ f Source #

The boundary of the face as a simple polygon. For internal faces the polygon that is reported has its vertices stored in CCW order (as expected).

pre: FaceId refers to an internal face.

For the other face this prodcuces a polygon in CW order (this may lead to unexpected results.)

runningtime: \(O(k)\), where \(k\) is the size of the face.

internalFacePolygon :: FaceId' s -> PlaneGraph s v e f r -> SimplePolygon v r :+ f Source #

The boundary of the face as a simple polygon. For internal faces the polygon that is reported has its vertices stored in CCW order (as expected).

pre: FaceId refers to an internal face.

For the other face this prodcuces a polygon in CW order (this may lead to unexpected results.)

runningtime: \(O(k)\), where \(k\) is the size of the face.

outerFacePolygon :: (Num r, Ord r) => FaceId' s -> PlaneGraph s v e f r -> MultiPolygon (Maybe v) r :+ f Source #

Given the outerFaceId and the graph, construct a sufficiently large rectangular multipolygon ith a hole containing the boundary of the outer face.

outerFacePolygon' :: FaceId' s -> SimplePolygon v' r -> PlaneGraph s v e f r -> MultiPolygon (Either v' v) r :+ f Source #

Given the outerface id, and a sufficiently large outer boundary, draw the outerface as a polygon with a hole.

facePolygons :: (Num r, Ord r) => FaceId' s -> PlaneGraph s v e f r -> ((FaceId' s, MultiPolygon (Maybe v) r :+ f), Vector (FaceId' s, SimplePolygon v r :+ f)) Source #

Given the outerFace Id, construct polygons for all faces. We construct a polygon with a hole for the outer face.

facePolygons' :: FaceId' s -> PlaneGraph s v e f r -> Vector (FaceId' s, SimplePolygon v r :+ f) Source #

Given the outerFace Id, lists all internal faces of the plane graph with their boundaries.

newtype VertexId (s :: k) (w :: World) #

A vertex in a planar graph. A vertex is tied to a particular planar graph by the phantom type s, and to a particular world w.

Constructors

VertexId 

Fields

Instances

Instances details
Incident (s :: k) (FaceId' s) (VertexId' s) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Basic

Methods

incidences :: PlanarSubdivision s v e f r -> FaceId' s -> [VertexId' s] Source #

Incident (s :: k) (Dart s) (VertexId' s) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Basic

Methods

incidences :: PlanarSubdivision s v e f r -> Dart s -> [VertexId' s] Source #

Incident (s :: k) (VertexId' s) (FaceId' s) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Basic

Methods

incidences :: PlanarSubdivision s v e f r -> VertexId' s -> [FaceId' s] Source #

Incident (s :: k) (VertexId' s) (Dart s) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Basic

Methods

incidences :: PlanarSubdivision s v e f r -> VertexId' s -> [Dart s] Source #

Enum (VertexId s w) 
Instance details

Defined in Data.PlanarGraph.Core

Methods

succ :: VertexId s w -> VertexId s w #

pred :: VertexId s w -> VertexId s w #

toEnum :: Int -> VertexId s w #

fromEnum :: VertexId s w -> Int #

enumFrom :: VertexId s w -> [VertexId s w] #

enumFromThen :: VertexId s w -> VertexId s w -> [VertexId s w] #

enumFromTo :: VertexId s w -> VertexId s w -> [VertexId s w] #

enumFromThenTo :: VertexId s w -> VertexId s w -> VertexId s w -> [VertexId s w] #

Eq (VertexId s w) 
Instance details

Defined in Data.PlanarGraph.Core

Methods

(==) :: VertexId s w -> VertexId s w -> Bool #

(/=) :: VertexId s w -> VertexId s w -> Bool #

Ord (VertexId s w) 
Instance details

Defined in Data.PlanarGraph.Core

Methods

compare :: VertexId s w -> VertexId s w -> Ordering #

(<) :: VertexId s w -> VertexId s w -> Bool #

(<=) :: VertexId s w -> VertexId s w -> Bool #

(>) :: VertexId s w -> VertexId s w -> Bool #

(>=) :: VertexId s w -> VertexId s w -> Bool #

max :: VertexId s w -> VertexId s w -> VertexId s w #

min :: VertexId s w -> VertexId s w -> VertexId s w #

Show (VertexId s w) 
Instance details

Defined in Data.PlanarGraph.Core

Methods

showsPrec :: Int -> VertexId s w -> ShowS #

show :: VertexId s w -> String #

showList :: [VertexId s w] -> ShowS #

Generic (VertexId s w) 
Instance details

Defined in Data.PlanarGraph.Core

Associated Types

type Rep (VertexId s w) :: Type -> Type #

Methods

from :: VertexId s w -> Rep (VertexId s w) x #

to :: Rep (VertexId s w) x -> VertexId s w #

ToJSON (VertexId s w) 
Instance details

Defined in Data.PlanarGraph.Core

FromJSON (VertexId s w) 
Instance details

Defined in Data.PlanarGraph.Core

NFData (VertexId s w) 
Instance details

Defined in Data.PlanarGraph.Core

Methods

rnf :: VertexId s w -> () #

HasDataOf (PlaneGraph s v e f r) (VertexId' s) Source # 
Instance details

Defined in Data.PlaneGraph.Core

Associated Types

type DataOf (PlaneGraph s v e f r) (VertexId' s) #

Methods

dataOf :: VertexId' s -> Lens' (PlaneGraph s v e f r) (DataOf (PlaneGraph s v e f r) (VertexId' s)) #

HasDataOf (PlanarSubdivision s v e f r) (VertexId' s) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Basic

Associated Types

type DataOf (PlanarSubdivision s v e f r) (VertexId' s) #

Methods

dataOf :: VertexId' s -> Lens' (PlanarSubdivision s v e f r) (DataOf (PlanarSubdivision s v e f r) (VertexId' s)) #

HasDataOf (PlanarGraph s w v e f) (VertexId s w) 
Instance details

Defined in Data.PlanarGraph.Core

Associated Types

type DataOf (PlanarGraph s w v e f) (VertexId s w) #

Methods

dataOf :: VertexId s w -> Lens' (PlanarGraph s w v e f) (DataOf (PlanarGraph s w v e f) (VertexId s w)) #

type Rep (VertexId s w) 
Instance details

Defined in Data.PlanarGraph.Core

type Rep (VertexId s w) = D1 ('MetaData "VertexId" "Data.PlanarGraph.Core" "hgeometry-combinatorial-0.14-4eKKoxfw4Iy23UosEmuxsr" 'True) (C1 ('MetaCons "VertexId" 'PrefixI 'True) (S1 ('MetaSel ('Just "_unVertexId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))
type DataOf (PlaneGraph s v e f r) (VertexId' s) Source # 
Instance details

Defined in Data.PlaneGraph.Core

type DataOf (PlaneGraph s v e f r) (VertexId' s) = v
type DataOf (PlanarSubdivision s v e f r) (VertexId' s) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Basic

type DataOf (PlanarSubdivision s v e f r) (VertexId' s) = v
type DataOf (PlanarGraph s w v e f) (VertexId s w) 
Instance details

Defined in Data.PlanarGraph.Core

type DataOf (PlanarGraph s w v e f) (VertexId s w) = v

newtype FaceId (s :: k) (w :: World) #

The type to represent FaceId's

Constructors

FaceId 

Fields

Instances

Instances details
Incident (s :: k) (FaceId' s) (Dart s) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Basic

Methods

incidences :: PlanarSubdivision s v e f r -> FaceId' s -> [Dart s] Source #

Incident (s :: k) (FaceId' s) (VertexId' s) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Basic

Methods

incidences :: PlanarSubdivision s v e f r -> FaceId' s -> [VertexId' s] Source #

Incident (s :: k) (Dart s) (FaceId' s) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Basic

Methods

incidences :: PlanarSubdivision s v e f r -> Dart s -> [FaceId' s] Source #

Incident (s :: k) (VertexId' s) (FaceId' s) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Basic

Methods

incidences :: PlanarSubdivision s v e f r -> VertexId' s -> [FaceId' s] Source #

Enum (FaceId s w) 
Instance details

Defined in Data.PlanarGraph.Core

Methods

succ :: FaceId s w -> FaceId s w #

pred :: FaceId s w -> FaceId s w #

toEnum :: Int -> FaceId s w #

fromEnum :: FaceId s w -> Int #

enumFrom :: FaceId s w -> [FaceId s w] #

enumFromThen :: FaceId s w -> FaceId s w -> [FaceId s w] #

enumFromTo :: FaceId s w -> FaceId s w -> [FaceId s w] #

enumFromThenTo :: FaceId s w -> FaceId s w -> FaceId s w -> [FaceId s w] #

Eq (FaceId s w) 
Instance details

Defined in Data.PlanarGraph.Core

Methods

(==) :: FaceId s w -> FaceId s w -> Bool #

(/=) :: FaceId s w -> FaceId s w -> Bool #

Ord (FaceId s w) 
Instance details

Defined in Data.PlanarGraph.Core

Methods

compare :: FaceId s w -> FaceId s w -> Ordering #

(<) :: FaceId s w -> FaceId s w -> Bool #

(<=) :: FaceId s w -> FaceId s w -> Bool #

(>) :: FaceId s w -> FaceId s w -> Bool #

(>=) :: FaceId s w -> FaceId s w -> Bool #

max :: FaceId s w -> FaceId s w -> FaceId s w #

min :: FaceId s w -> FaceId s w -> FaceId s w #

Show (FaceId s w) 
Instance details

Defined in Data.PlanarGraph.Core

Methods

showsPrec :: Int -> FaceId s w -> ShowS #

show :: FaceId s w -> String #

showList :: [FaceId s w] -> ShowS #

ToJSON (FaceId s w) 
Instance details

Defined in Data.PlanarGraph.Core

Methods

toJSON :: FaceId s w -> Value #

toEncoding :: FaceId s w -> Encoding #

toJSONList :: [FaceId s w] -> Value #

toEncodingList :: [FaceId s w] -> Encoding #

FromJSON (FaceId s w) 
Instance details

Defined in Data.PlanarGraph.Core

Methods

parseJSON :: Value -> Parser (FaceId s w) #

parseJSONList :: Value -> Parser [FaceId s w] #

HasDataOf (PlaneGraph s v e f r) (FaceId' s) Source # 
Instance details

Defined in Data.PlaneGraph.Core

Associated Types

type DataOf (PlaneGraph s v e f r) (FaceId' s) #

Methods

dataOf :: FaceId' s -> Lens' (PlaneGraph s v e f r) (DataOf (PlaneGraph s v e f r) (FaceId' s)) #

HasDataOf (PlanarSubdivision s v e f r) (FaceId' s) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Basic

Associated Types

type DataOf (PlanarSubdivision s v e f r) (FaceId' s) #

Methods

dataOf :: FaceId' s -> Lens' (PlanarSubdivision s v e f r) (DataOf (PlanarSubdivision s v e f r) (FaceId' s)) #

HasDataOf (PlanarGraph s w v e f) (FaceId s w) 
Instance details

Defined in Data.PlanarGraph.Core

Associated Types

type DataOf (PlanarGraph s w v e f) (FaceId s w) #

Methods

dataOf :: FaceId s w -> Lens' (PlanarGraph s w v e f) (DataOf (PlanarGraph s w v e f) (FaceId s w)) #

type DataOf (PlaneGraph s v e f r) (FaceId' s) Source # 
Instance details

Defined in Data.PlaneGraph.Core

type DataOf (PlaneGraph s v e f r) (FaceId' s) = f
type DataOf (PlanarSubdivision s v e f r) (FaceId' s) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Basic

type DataOf (PlanarSubdivision s v e f r) (FaceId' s) = f
type DataOf (PlanarGraph s w v e f) (FaceId s w) 
Instance details

Defined in Data.PlanarGraph.Core

type DataOf (PlanarGraph s w v e f) (FaceId s w) = f

data Dart (s :: k) #

A dart represents a bi-directed edge. I.e. a dart has a direction, however the dart of the oposite direction is always present in the planar graph as well.

Instances

Instances details
Incident (s :: k) (FaceId' s) (Dart s) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Basic

Methods

incidences :: PlanarSubdivision s v e f r -> FaceId' s -> [Dart s] Source #

Incident (s :: k) (Dart s) (FaceId' s) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Basic

Methods

incidences :: PlanarSubdivision s v e f r -> Dart s -> [FaceId' s] Source #

Incident (s :: k) (Dart s) (VertexId' s) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Basic

Methods

incidences :: PlanarSubdivision s v e f r -> Dart s -> [VertexId' s] Source #

Incident (s :: k) (VertexId' s) (Dart s) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Basic

Methods

incidences :: PlanarSubdivision s v e f r -> VertexId' s -> [Dart s] Source #

Enum (Dart s) 
Instance details

Defined in Data.PlanarGraph.Dart

Methods

succ :: Dart s -> Dart s #

pred :: Dart s -> Dart s #

toEnum :: Int -> Dart s #

fromEnum :: Dart s -> Int #

enumFrom :: Dart s -> [Dart s] #

enumFromThen :: Dart s -> Dart s -> [Dart s] #

enumFromTo :: Dart s -> Dart s -> [Dart s] #

enumFromThenTo :: Dart s -> Dart s -> Dart s -> [Dart s] #

Eq (Dart s) 
Instance details

Defined in Data.PlanarGraph.Dart

Methods

(==) :: Dart s -> Dart s -> Bool #

(/=) :: Dart s -> Dart s -> Bool #

Ord (Dart s) 
Instance details

Defined in Data.PlanarGraph.Dart

Methods

compare :: Dart s -> Dart s -> Ordering #

(<) :: Dart s -> Dart s -> Bool #

(<=) :: Dart s -> Dart s -> Bool #

(>) :: Dart s -> Dart s -> Bool #

(>=) :: Dart s -> Dart s -> Bool #

max :: Dart s -> Dart s -> Dart s #

min :: Dart s -> Dart s -> Dart s #

Show (Dart s) 
Instance details

Defined in Data.PlanarGraph.Dart

Methods

showsPrec :: Int -> Dart s -> ShowS #

show :: Dart s -> String #

showList :: [Dart s] -> ShowS #

Generic (Dart s) 
Instance details

Defined in Data.PlanarGraph.Dart

Associated Types

type Rep (Dart s) :: Type -> Type #

Methods

from :: Dart s -> Rep (Dart s) x #

to :: Rep (Dart s) x -> Dart s #

Arbitrary (Dart s) 
Instance details

Defined in Data.PlanarGraph.Dart

Methods

arbitrary :: Gen (Dart s) #

shrink :: Dart s -> [Dart s] #

NFData (Dart s) 
Instance details

Defined in Data.PlanarGraph.Dart

Methods

rnf :: Dart s -> () #

HasDataOf (PlanarGraph s w v e f) (Dart s) 
Instance details

Defined in Data.PlanarGraph.Core

Associated Types

type DataOf (PlanarGraph s w v e f) (Dart s) #

Methods

dataOf :: Dart s -> Lens' (PlanarGraph s w v e f) (DataOf (PlanarGraph s w v e f) (Dart s)) #

HasDataOf (PlaneGraph s v e f r) (Dart s) Source # 
Instance details

Defined in Data.PlaneGraph.Core

Associated Types

type DataOf (PlaneGraph s v e f r) (Dart s) #

Methods

dataOf :: Dart s -> Lens' (PlaneGraph s v e f r) (DataOf (PlaneGraph s v e f r) (Dart s)) #

HasDataOf (PlanarSubdivision s v e f r) (Dart s) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Basic

Associated Types

type DataOf (PlanarSubdivision s v e f r) (Dart s) #

Methods

dataOf :: Dart s -> Lens' (PlanarSubdivision s v e f r) (DataOf (PlanarSubdivision s v e f r) (Dart s)) #

type Rep (Dart s) 
Instance details

Defined in Data.PlanarGraph.Dart

type Rep (Dart s) = D1 ('MetaData "Dart" "Data.PlanarGraph.Dart" "hgeometry-combinatorial-0.14-4eKKoxfw4Iy23UosEmuxsr" 'False) (C1 ('MetaCons "Dart" 'PrefixI 'True) (S1 ('MetaSel ('Just "_arc") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Arc s)) :*: S1 ('MetaSel ('Just "_direction") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Direction)))
type DataOf (PlanarGraph s w v e f) (Dart s) 
Instance details

Defined in Data.PlanarGraph.Core

type DataOf (PlanarGraph s w v e f) (Dart s) = e
type DataOf (PlaneGraph s v e f r) (Dart s) Source # 
Instance details

Defined in Data.PlaneGraph.Core

type DataOf (PlaneGraph s v e f r) (Dart s) = e
type DataOf (PlanarSubdivision s v e f r) (Dart s) Source # 
Instance details

Defined in Data.Geometry.PlanarSubdivision.Basic

type DataOf (PlanarSubdivision s v e f r) (Dart s) = e

data World #

The world in which the graph lives

Constructors

Primal 
Dual 

Instances

Instances details
Eq World 
Instance details

Defined in Data.PlanarGraph.Core

Methods

(==) :: World -> World -> Bool #

(/=) :: World -> World -> Bool #

Show World 
Instance details

Defined in Data.PlanarGraph.Core

Methods

showsPrec :: Int -> World -> ShowS #

show :: World -> String #

showList :: [World] -> ShowS #

type VertexId' (s :: k) = VertexId s 'Primal #

Shorthand for vertices in the primal.

type FaceId' (s :: k) = FaceId s 'Primal #

Shorthand for FaceId's in the primal.

withEdgeDistances :: (Point 2 r -> Point 2 r -> a) -> PlaneGraph s p e f r -> PlaneGraph s p (a :+ e) f r Source #

Labels the edges of a plane graph with their distances, as specified by the distance function.

writePlaneGraph :: (ToJSON v, ToJSON e, ToJSON f, ToJSON r) => PlaneGraph s v e f r -> ByteString Source #

Writes a plane graph to a bytestring

readPlaneGraph :: forall s v e f r. (FromJSON v, FromJSON e, FromJSON f, FromJSON r) => ByteString -> Either ParseException (PlaneGraph s v e f r) Source #

Reads a plane graph from a bytestring