hgeometry-0.8.0.0: Geometric Algorithms, Data structures, and Data types.

Copyright(C) Frank Staals
Licensesee the LICENSE file
MaintainerFrank Staals
Safe HaskellNone
LanguageHaskell2010

Data.PlanarGraph

Contents

Description

Data type for representing connected planar graphs

Synopsis

Documentation

>>> :{
let dart i s = Dart (Arc i) (read s)
    (aA:aB:aC:aD:aE:aG:_) = take 6 [Arc 0..]
    myGraph :: PlanarGraph () Primal () String ()
    myGraph = planarGraph [ [ (Dart aA Negative, "a-")
                            , (Dart aC Positive, "c+")
                            , (Dart aB Positive, "b+")
                            , (Dart aA Positive, "a+")
                            ]
                          , [ (Dart aE Negative, "e-")
                            , (Dart aB Negative, "b-")
                            , (Dart aD Negative, "d-")
                            , (Dart aG Positive, "g+")
                            ]
                          , [ (Dart aE Positive, "e+")
                            , (Dart aD Positive, "d+")
                            , (Dart aC Negative, "c-")
                            ]
                          , [ (Dart aG Negative, "g-")
                            ]
                          ]
:}

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.

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

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
(Eq v, Eq e, Eq f) => Eq (PlanarGraph s w v e f) Source # 
Instance details

Defined in Data.PlanarGraph

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) Source # 
Instance details

Defined in Data.PlanarGraph

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) Source # 
Instance details

Defined in Data.PlanarGraph

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 #

(ToJSON v, ToJSON e, ToJSON f) => ToJSON (PlanarGraph s w v e f) Source # 
Instance details

Defined in Data.PlanarGraph

Methods

toJSON :: PlanarGraph s w v e f -> Value #

toEncoding :: PlanarGraph s w v e f -> Encoding #

toJSONList :: [PlanarGraph s w v e f] -> Value #

toEncodingList :: [PlanarGraph s w v e f] -> Encoding #

(FromJSON v, FromJSON e, FromJSON f) => FromJSON (PlanarGraph s Primal v e f) Source # 
Instance details

Defined in Data.PlanarGraph

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

Defined in Data.PlanarGraph

Associated Types

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

Methods

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

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

Defined in Data.PlanarGraph

Associated Types

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

Methods

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

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

Defined in Data.PlanarGraph

Associated Types

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

Methods

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

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

Defined in Data.PlanarGraph

type Rep (PlanarGraph s w v e f) = D1 (MetaData "PlanarGraph" "Data.PlanarGraph" "hgeometry-0.8.0.0-2B18HmKepFxHOPvqiUEkND" 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) Source # 
Instance details

Defined in Data.PlanarGraph

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

Defined in Data.PlanarGraph

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

Defined in Data.PlanarGraph

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

embedding :: Getter (PlanarGraph s w v e f) (Permutation (Dart s)) Source #

Get the embedding, reprsented as a permutation of the darts, of this graph.

vertexData :: Lens (PlanarGraph s w v e f) (PlanarGraph s w v' e f) (Vector v) (Vector v') Source #

dartData :: Lens (PlanarGraph s w v e f) (PlanarGraph s w v e' f) (Vector (Dart s, e)) (Vector (Dart s, e')) Source #

lens to access the Dart Data

faceData :: Lens (PlanarGraph s w v e f) (PlanarGraph s w v e f') (Vector f) (Vector f') Source #

rawDartData :: Lens (PlanarGraph s w v e f) (PlanarGraph s w v e' f) (Vector e) (Vector e') Source #

edgeData :: Lens (PlanarGraph s w v e f) (PlanarGraph s w v e' f) (Vector (Dart s, e)) (Vector (Dart s, e')) Source #

edgeData is just an alias for dartData

data World Source #

The world in which the graph lives

Constructors

Primal 
Dual 
Instances
Eq World Source # 
Instance details

Defined in Data.PlanarGraph

Methods

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

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

Show World Source # 
Instance details

Defined in Data.PlanarGraph

Methods

showsPrec :: Int -> World -> ShowS #

show :: World -> String #

showList :: [World] -> ShowS #

type family DualOf (sp :: World) where ... Source #

We can take the dual of a world. For the Primal this gives us the Dual, for the Dual this gives us the Primal.

Representing edges: Arcs and Darts

newtype Arc s Source #

An Arc is a directed edge in a planar graph. The type s is used to tie this arc to a particular graph.

Constructors

Arc 

Fields

Instances
Bounded (Arc s) Source # 
Instance details

Defined in Data.PlanarGraph

Methods

minBound :: Arc s #

maxBound :: Arc s #

Enum (Arc s) Source # 
Instance details

Defined in Data.PlanarGraph

Methods

succ :: Arc s -> Arc s #

pred :: Arc s -> Arc s #

toEnum :: Int -> Arc s #

fromEnum :: Arc s -> Int #

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

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

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

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

Eq (Arc s) Source # 
Instance details

Defined in Data.PlanarGraph

Methods

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

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

Ord (Arc s) Source # 
Instance details

Defined in Data.PlanarGraph

Methods

compare :: Arc s -> Arc s -> Ordering #

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

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

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

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

max :: Arc s -> Arc s -> Arc s #

min :: Arc s -> Arc s -> Arc s #

Show (Arc s) Source # 
Instance details

Defined in Data.PlanarGraph

Methods

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

show :: Arc s -> String #

showList :: [Arc s] -> ShowS #

Generic (Arc s) Source # 
Instance details

Defined in Data.PlanarGraph

Associated Types

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

Methods

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

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

Arbitrary (Arc s) Source # 
Instance details

Defined in Test.QuickCheck.HGeometryInstances

Methods

arbitrary :: Gen (Arc s) #

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

NFData (Arc s) Source # 
Instance details

Defined in Data.PlanarGraph

Methods

rnf :: Arc s -> () #

type Rep (Arc s) Source # 
Instance details

Defined in Data.PlanarGraph

type Rep (Arc s) = D1 (MetaData "Arc" "Data.PlanarGraph" "hgeometry-0.8.0.0-2B18HmKepFxHOPvqiUEkND" True) (C1 (MetaCons "Arc" PrefixI True) (S1 (MetaSel (Just "_unArc") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))

data Direction Source #

Darts have a direction which is either Positive or Negative (shown as +1 or -1, respectively).

Constructors

Negative 
Positive 
Instances
Bounded Direction Source # 
Instance details

Defined in Data.PlanarGraph

Enum Direction Source # 
Instance details

Defined in Data.PlanarGraph

Eq Direction Source # 
Instance details

Defined in Data.PlanarGraph

Ord Direction Source # 
Instance details

Defined in Data.PlanarGraph

Read Direction Source # 
Instance details

Defined in Data.PlanarGraph

Show Direction Source # 
Instance details

Defined in Data.PlanarGraph

Generic Direction Source # 
Instance details

Defined in Data.PlanarGraph

Associated Types

type Rep Direction :: Type -> Type #

Arbitrary Direction Source # 
Instance details

Defined in Test.QuickCheck.HGeometryInstances

NFData Direction Source # 
Instance details

Defined in Data.PlanarGraph

Methods

rnf :: Direction -> () #

type Rep Direction Source # 
Instance details

Defined in Data.PlanarGraph

type Rep Direction = D1 (MetaData "Direction" "Data.PlanarGraph" "hgeometry-0.8.0.0-2B18HmKepFxHOPvqiUEkND" False) (C1 (MetaCons "Negative" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Positive" PrefixI False) (U1 :: Type -> Type))

rev :: Direction -> Direction Source #

Reverse the direcion

data Dart s Source #

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.

Constructors

Dart 

Fields

Instances
Enum (Dart s) Source # 
Instance details

Defined in Data.PlanarGraph

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) Source # 
Instance details

Defined in Data.PlanarGraph

Methods

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

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

Ord (Dart s) Source # 
Instance details

Defined in Data.PlanarGraph

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) Source # 
Instance details

Defined in Data.PlanarGraph

Methods

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

show :: Dart s -> String #

showList :: [Dart s] -> ShowS #

Generic (Dart s) Source # 
Instance details

Defined in Data.PlanarGraph

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) Source # 
Instance details

Defined in Test.QuickCheck.HGeometryInstances

Methods

arbitrary :: Gen (Dart s) #

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

NFData (Dart s) Source # 
Instance details

Defined in Data.PlanarGraph

Methods

rnf :: Dart s -> () #

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

Defined in Data.PlanarGraph

Associated Types

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

Methods

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

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

Defined in Data.PlaneGraph

Associated Types

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

Methods

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

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) :: Type Source #

Methods

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

type Rep (Dart s) Source # 
Instance details

Defined in Data.PlanarGraph

type Rep (Dart s) = D1 (MetaData "Dart" "Data.PlanarGraph" "hgeometry-0.8.0.0-2B18HmKepFxHOPvqiUEkND" 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) Source # 
Instance details

Defined in Data.PlanarGraph

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

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

arc :: forall s s. Lens (Dart s) (Dart s) (Arc s) (Arc s) Source #

twin :: Dart s -> Dart s Source #

Get the twin of this dart (edge)

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

isPositive :: Dart s -> Bool Source #

test if a dart is Positive

Vertices

newtype VertexId s (w :: World) Source #

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
Enum (VertexId s w) Source # 
Instance details

Defined in Data.PlanarGraph

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) Source # 
Instance details

Defined in Data.PlanarGraph

Methods

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

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

Ord (VertexId s w) Source # 
Instance details

Defined in Data.PlanarGraph

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) Source # 
Instance details

Defined in Data.PlanarGraph

Methods

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

show :: VertexId s w -> String #

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

Generic (VertexId s w) Source # 
Instance details

Defined in Data.PlanarGraph

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) Source # 
Instance details

Defined in Data.PlanarGraph

FromJSON (VertexId s w) Source # 
Instance details

Defined in Data.PlanarGraph

NFData (VertexId s w) Source # 
Instance details

Defined in Data.PlanarGraph

Methods

rnf :: VertexId s w -> () #

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

Defined in Data.PlaneGraph

Associated Types

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

Methods

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

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) :: Type Source #

Methods

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

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

Defined in Data.PlanarGraph

Associated Types

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

Methods

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

type Rep (VertexId s w) Source # 
Instance details

Defined in Data.PlanarGraph

type Rep (VertexId s w) = D1 (MetaData "VertexId" "Data.PlanarGraph" "hgeometry-0.8.0.0-2B18HmKepFxHOPvqiUEkND" 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

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) Source # 
Instance details

Defined in Data.PlanarGraph

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

type VertexId' s = VertexId s Primal Source #

Shorthand for vertices in the primal.

Building a planar graph

planarGraph :: [[(Dart s, e)]] -> PlanarGraph s Primal () e () Source #

Construct a planar graph, given the darts in cyclic order around each vertex.

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

planarGraph' :: Permutation (Dart s) -> PlanarGraph s w () () () Source #

Construct a planar graph

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

fromAdjacencyLists :: forall s w h. (Foldable h, Functor h) => [(VertexId s w, h (VertexId s w))] -> PlanarGraph s w () () () Source #

Construct a planar graph from a adjacency matrix. For every vertex, all vertices should be given in counter clockwise order.

pre: No self-loops, and no multi-edges

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

toAdjacencyLists :: PlanarGraph s w v e f -> [(VertexId s w, Vector (VertexId s w))] Source #

Produces the adjacencylists for all vertices in the graph. For every vertex, the adjacent vertices are given in counter clockwise order.

Note that in case a vertex u as a self loop, we have that this vertexId occurs twice in the list of neighbours, i.e.: u : [...,u,..,u,...]. Similarly, if there are multiple darts between a pair of edges they occur multiple times.

running time: \(O(n)\)

buildFromJSON :: Vector (VertexId' s :+ v) -> Vector ((VertexId' s, VertexId' s) :+ e) -> Vector (FaceId' s :+ f) -> [(VertexId' s, Vector (VertexId' s))] -> PlanarGraph s Primal v e f Source #

Helper function to build the graph from JSON data

running time: \(O(n)\)

Quering a planar graph

numVertices :: PlanarGraph s w v e f -> Int Source #

Get the number of vertices

>>> numVertices myGraph
4

numDarts :: PlanarGraph s w v e f -> Int Source #

Get the number of Darts

>>> numDarts myGraph
12

numEdges :: PlanarGraph s w v e f -> Int Source #

Get the number of Edges

>>> numEdges myGraph
6

numFaces :: PlanarGraph s w v e f -> Int Source #

Get the number of faces

>>> numFaces myGraph
4

darts' :: PlanarGraph s w v e f -> Vector (Dart s) Source #

Enumerate all darts

darts :: PlanarGraph s w v e f -> Vector (Dart s, e) Source #

Get all darts together with their data

>>> mapM_ print $ darts myGraph
(Dart (Arc 0) -1,"a-")
(Dart (Arc 2) +1,"c+")
(Dart (Arc 1) +1,"b+")
(Dart (Arc 0) +1,"a+")
(Dart (Arc 4) -1,"e-")
(Dart (Arc 1) -1,"b-")
(Dart (Arc 3) -1,"d-")
(Dart (Arc 5) +1,"g+")
(Dart (Arc 4) +1,"e+")
(Dart (Arc 3) +1,"d+")
(Dart (Arc 2) -1,"c-")
(Dart (Arc 5) -1,"g-")

edges' :: PlanarGraph s w v e f -> Vector (Dart s) Source #

Enumerate all edges. We report only the Positive darts

edges :: PlanarGraph s w v e f -> Vector (Dart s, e) Source #

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

>>> mapM_ print $ edges myGraph
(Dart (Arc 2) +1,"c+")
(Dart (Arc 1) +1,"b+")
(Dart (Arc 0) +1,"a+")
(Dart (Arc 5) +1,"g+")
(Dart (Arc 4) +1,"e+")
(Dart (Arc 3) +1,"d+")

vertices' :: PlanarGraph s w v e f -> Vector (VertexId s w) Source #

Enumerate all vertices

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

vertices :: PlanarGraph s w v e f -> Vector (VertexId s w, v) Source #

Enumerate all vertices, together with their vertex data

faces' :: PlanarGraph s w v e f -> Vector (FaceId s w) Source #

Enumerate all faces in the planar graph

faces :: PlanarGraph s w v e f -> Vector (FaceId s w, f) Source #

All faces with their face data.

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

Traverse the vertices

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

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

Traverses the darts

>>> traverseDarts (\d x -> print (d,x)) myGraph >> pure ()
(Dart (Arc 0) +1,"a+")
(Dart (Arc 0) -1,"a-")
(Dart (Arc 1) +1,"b+")
(Dart (Arc 1) -1,"b-")
(Dart (Arc 2) +1,"c+")
(Dart (Arc 2) -1,"c-")
(Dart (Arc 3) +1,"d+")
(Dart (Arc 3) -1,"d-")
(Dart (Arc 4) +1,"e+")
(Dart (Arc 4) -1,"e-")
(Dart (Arc 5) +1,"g+")
(Dart (Arc 5) -1,"g-")

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

Traverses the faces

>>> traverseFaces (\i x -> print (i,x)) myGraph >> pure ()
(FaceId 0,())
(FaceId 1,())
(FaceId 2,())
(FaceId 3,())

tailOf :: Dart s -> PlanarGraph s w v e f -> VertexId s w Source #

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

running time: \(O(1)\)

headOf :: Dart s -> PlanarGraph s w v e f -> VertexId s w Source #

The vertex this dart is heading in to

running time: \(O(1)\)

endPoints :: Dart s -> PlanarGraph s w v e f -> (VertexId s w, VertexId s w) Source #

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

running time: \(O(1)\)

incidentEdges :: VertexId s w -> PlanarGraph s w v e f -> 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

incomingEdges :: VertexId s w -> PlanarGraph s w v e f -> Vector (Dart s) Source #

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

outgoingEdges :: VertexId s w -> PlanarGraph s w v e f -> Vector (Dart s) Source #

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

neighboursOf :: VertexId s w -> PlanarGraph s w v e f -> Vector (VertexId s w) Source #

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

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

nextIncidentEdge :: Dart s -> PlanarGraph s w v e f -> Dart s Source #

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

running time: \(O(1)\)

prevIncidentEdge :: Dart s -> PlanarGraph s w v e f -> Dart s Source #

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

running time: \(O(1)\)

Associated Data

class HasDataOf g i where Source #

Associated Types

type DataOf g i Source #

Methods

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

get the data associated with the value i.

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

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

Defined in Data.PlanarGraph

Associated Types

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

Methods

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

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

Defined in Data.PlaneGraph

Associated Types

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

Methods

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

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

Defined in Data.PlaneGraph

Associated Types

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

Methods

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

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

Defined in Data.PlaneGraph

Associated Types

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

Methods

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

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) :: Type Source #

Methods

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

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) :: Type Source #

Methods

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

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) :: Type Source #

Methods

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

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

Defined in Data.PlanarGraph

Associated Types

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

Methods

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

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

Defined in Data.PlanarGraph

Associated Types

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

Methods

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

endPointDataOf :: Dart s -> Getter (PlanarGraph s w v e f) (v, v) Source #

Data corresponding to the endpoints of the dart

endPointData :: Dart s -> PlanarGraph s w v e f -> (v, v) Source #

Data corresponding to the endpoints of the dart

running time: \(O(1)\)

dual :: Getter (PlanarGraph s w v e f) (PlanarGraph s (DualOf w) f e v) Source #

Get the dual graph of this graph.

Faces

newtype FaceId s w Source #

The type to reprsent FaceId's

Constructors

FaceId 

Fields

Instances
Enum (FaceId s w) Source # 
Instance details

Defined in Data.PlanarGraph

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) Source # 
Instance details

Defined in Data.PlanarGraph

Methods

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

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

Ord (FaceId s w) Source # 
Instance details

Defined in Data.PlanarGraph

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) Source # 
Instance details

Defined in Data.PlanarGraph

Methods

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

show :: FaceId s w -> String #

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

ToJSON (FaceId s w) Source # 
Instance details

Defined in Data.PlanarGraph

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) Source # 
Instance details

Defined in Data.PlanarGraph

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

Associated Types

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

Methods

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

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) :: Type Source #

Methods

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

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

Defined in Data.PlanarGraph

Associated Types

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

Methods

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

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

Defined in Data.PlaneGraph

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) Source # 
Instance details

Defined in Data.PlanarGraph

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

type FaceId' s = FaceId s Primal Source #

Shorthand for FaceId's in the primal.

leftFace :: Dart s -> PlanarGraph s w v e f -> FaceId s w Source #

The face to the left of the dart

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

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

rightFace :: Dart s -> PlanarGraph s w v e f -> FaceId s w Source #

The face to the right of the dart

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

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

boundaryDart :: FaceId s w -> PlanarGraph s w v e f -> 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.

boundary :: FaceId s w -> PlanarGraph s w v e f -> Vector (Dart s) Source #

The darts 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.

boundary' :: Dart s -> PlanarGraph s w v e f -> Vector (Dart s) Source #

Generates the darts incident to a face, starting with the given dart.

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

boundaryVertices :: FaceId s w -> PlanarGraph s w v e f -> Vector (VertexId s w) 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.

nextEdge :: Dart s -> PlanarGraph s w v e f -> Dart s Source #

Get the next edge along the face

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

prevEdge :: Dart s -> PlanarGraph s w v e f -> Dart s Source #

Get the previous edge along the face

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

Edge Oracle

data EdgeOracle s w a Source #

Edge Oracle:

main idea: store adjacency lists in such a way that we store an edge (u,v) either in u's adjacency list or in v's. This can be done s.t. all adjacency lists have length at most 6.

note: Every edge is stored exactly once (i.e. either at u or at v, but not both)

Instances
Functor (EdgeOracle s w) Source # 
Instance details

Defined in Data.PlanarGraph

Methods

fmap :: (a -> b) -> EdgeOracle s w a -> EdgeOracle s w b #

(<$) :: a -> EdgeOracle s w b -> EdgeOracle s w a #

Foldable (EdgeOracle s w) Source # 
Instance details

Defined in Data.PlanarGraph

Methods

fold :: Monoid m => EdgeOracle s w m -> m #

foldMap :: Monoid m => (a -> m) -> EdgeOracle s w a -> m #

foldr :: (a -> b -> b) -> b -> EdgeOracle s w a -> b #

foldr' :: (a -> b -> b) -> b -> EdgeOracle s w a -> b #

foldl :: (b -> a -> b) -> b -> EdgeOracle s w a -> b #

foldl' :: (b -> a -> b) -> b -> EdgeOracle s w a -> b #

foldr1 :: (a -> a -> a) -> EdgeOracle s w a -> a #

foldl1 :: (a -> a -> a) -> EdgeOracle s w a -> a #

toList :: EdgeOracle s w a -> [a] #

null :: EdgeOracle s w a -> Bool #

length :: EdgeOracle s w a -> Int #

elem :: Eq a => a -> EdgeOracle s w a -> Bool #

maximum :: Ord a => EdgeOracle s w a -> a #

minimum :: Ord a => EdgeOracle s w a -> a #

sum :: Num a => EdgeOracle s w a -> a #

product :: Num a => EdgeOracle s w a -> a #

Traversable (EdgeOracle s w) Source # 
Instance details

Defined in Data.PlanarGraph

Methods

traverse :: Applicative f => (a -> f b) -> EdgeOracle s w a -> f (EdgeOracle s w b) #

sequenceA :: Applicative f => EdgeOracle s w (f a) -> f (EdgeOracle s w a) #

mapM :: Monad m => (a -> m b) -> EdgeOracle s w a -> m (EdgeOracle s w b) #

sequence :: Monad m => EdgeOracle s w (m a) -> m (EdgeOracle s w a) #

Eq a => Eq (EdgeOracle s w a) Source # 
Instance details

Defined in Data.PlanarGraph

Methods

(==) :: EdgeOracle s w a -> EdgeOracle s w a -> Bool #

(/=) :: EdgeOracle s w a -> EdgeOracle s w a -> Bool #

Show a => Show (EdgeOracle s w a) Source # 
Instance details

Defined in Data.PlanarGraph

Methods

showsPrec :: Int -> EdgeOracle s w a -> ShowS #

show :: EdgeOracle s w a -> String #

showList :: [EdgeOracle s w a] -> ShowS #

edgeOracle :: PlanarGraph s w v e f -> EdgeOracle s w (Dart s) Source #

Given a planar graph, construct an edge oracle. Given a pair of vertices this allows us to efficiently find the dart representing this edge in the graph.

pre: No self-loops and no multi-edges!!!

running time: \(O(n)\)

buildEdgeOracle :: forall f s w e. Foldable f => [(VertexId s w, f (VertexId s w :+ e))] -> EdgeOracle s w e Source #

Builds an edge oracle that can be used to efficiently test if two vertices are connected by an edge.

running time: \(O(n)\)

findEdge :: VertexId s w -> VertexId s w -> EdgeOracle s w a -> Maybe a Source #

Find the edge data corresponding to edge (u,v) if such an edge exists

running time: \(O(1)\)

hasEdge :: VertexId s w -> VertexId s w -> EdgeOracle s w a -> Bool Source #

Test if u and v are connected by an edge.

running time: \(O(1)\)

findDart :: VertexId s w -> VertexId s w -> EdgeOracle s w (Dart s) -> Maybe (Dart s) Source #

Given a pair of vertices (u,v) returns the dart, oriented from u to v, corresponding to these vertices.

running time: \(O(1)\)

allDarts :: [Dart s] Source #

Enumerates all darts such that allDarts !! i = d = i == fromEnum d