hgeometry-combinatorial-0.9.0.0: Data structures, and Data types.

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

Data.PlanarGraph.Core

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.

Representing The World

data World Source #

The world in which the graph lives

Constructors

Primal 
Dual 
Instances
Eq World Source # 
Instance details

Defined in Data.PlanarGraph.Core

Methods

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

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

Show World Source # 
Instance details

Defined in Data.PlanarGraph.Core

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.

dualDualIdentity :: forall w. DualOf (DualOf w) :~: w Source #

The Dual of the Dual is the Primal.

VertexId's

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

Defined in Data.PlanarGraph.Core

FromJSON (VertexId s w) Source # 
Instance details

Defined in Data.PlanarGraph.Core

NFData (VertexId s w) Source # 
Instance details

Defined in Data.PlanarGraph.Core

Methods

rnf :: VertexId s w -> () #

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

Defined in Data.PlanarGraph.Core

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.Core

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

Defined in Data.PlanarGraph.Core

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.

FaceId's

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

Defined in Data.PlanarGraph.Core

Methods

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

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

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

Defined in Data.PlanarGraph.Core

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

Defined in Data.PlanarGraph.Core

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.

The graph type itself

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.

Constructors

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

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

Defined in Data.PlanarGraph.IO

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.IO

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

Defined in Data.PlanarGraph.Core

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

Defined in Data.PlanarGraph.Core

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 #

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

Defined in Data.PlanarGraph.Core

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

Defined in Data.PlanarGraph.Core

type Rep (PlanarGraph s w v e f) = D1 (MetaData "PlanarGraph" "Data.PlanarGraph.Core" "hgeometry-combinatorial-0.9.0.0-6qy5VaQ7muxJuEfibyCL9S" 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.Core

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

Defined in Data.PlanarGraph.Core

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

Defined in Data.PlanarGraph.Core

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

lenses and getters

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 #

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

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

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

Get the dual graph of this graph.

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

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

updateData :: forall s w v e f v' e' f'. (Vector v -> Vector v') -> (Vector e -> Vector e') -> (Vector f -> Vector f') -> PlanarGraph s w v e f -> PlanarGraph s w v' e' f' Source #

Helper function to update the data in a planar graph. Takes care to update both the data in the original graph as well as in the dual.

updateData' :: DualOf (DualOf w) ~ w => (Vector v -> Vector v') -> (Vector e -> Vector e') -> (Vector f -> Vector f') -> PlanarGraph s w v e f -> PlanarGraph s w v' e' f' Source #

The function that does the actual work for updateData

reorderEdgeData :: Foldable f => f (Dart s, e) -> Vector e Source #

Reorders the edge data to be in the right order to set edgeData

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,())

Constructing a Planar graph

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

Construct a planar graph

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

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)\).

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)\)

Convenience functions

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

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

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+")

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)\)

Access 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.Core

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

Defined in Data.PlanarGraph.Core

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 #

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

Defined in Data.PlanarGraph.Core

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 #

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)\)

The Dual graph

computeDual :: forall s w v e f. PlanarGraph s w v e f -> PlanarGraph s (DualOf w) f e v Source #

The dual of this graph

>>> :{
 let fromList = V.fromList
     answer = fromList [ fromList [dart 0 "-1"]
                       , fromList [dart 2 "+1",dart 4 "+1",dart 1 "-1",dart 0 "+1"]
                       , fromList [dart 1 "+1",dart 3 "-1",dart 2 "-1"]
                       , fromList [dart 4 "-1",dart 3 "+1",dart 5 "+1",dart 5 "-1"]
                       ]
 in (computeDual myGraph)^.embedding.orbits == answer
:}
True

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

computeDual' :: DualOf (DualOf w) ~ w => PlanarGraph s w v e f -> PlanarGraph s (DualOf w) f e v Source #

Does the actual work for dualGraph