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

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

Data.PlanarGraph.EdgeOracle

Description

Data structure to represent a planar graph with which we can test in \(O(1)\) time if an edge between a pair of vertices exists.

Synopsis

Documentation

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

Constructors

EdgeOracle 

Fields

Instances
Functor (EdgeOracle s w) Source # 
Instance details

Defined in Data.PlanarGraph.EdgeOracle

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

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

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

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

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

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

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

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