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

Safe HaskellNone
LanguageHaskell2010

Data.PlaneGraph

Synopsis

Documentation

newtype PlaneGraph s v e f r Source #

Embedded, *connected*, planar graph

Constructors

PlaneGraph (PlanarGraph s Primal (VertexData r v) e f) 
Instances
Functor (PlaneGraph s v e f) Source # 
Instance details

Defined in Data.PlaneGraph

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

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

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 #

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

Defined in Data.PlaneGraph

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 r, FromJSON v, FromJSON e, FromJSON f) => FromJSON (PlaneGraph s v e f r) Source # 
Instance details

Defined in Data.PlaneGraph

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

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

Associated Types

type DataOf (PlaneGraph s v e f r) (FaceId' s) :: * 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) :: * 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) :: * Source #

Methods

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

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

Defined in Data.PlaneGraph

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

Defined in Data.PlaneGraph

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

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

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

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

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

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 #

(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) :: * 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) :: * 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) :: * 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) (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

data VertexData r v Source #

Note that the functor instance is in v

Constructors

VertexData !(Point 2 r) !v 
Instances
Bifunctor VertexData Source # 
Instance details

Defined in Data.PlaneGraph

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

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

Methods

fold :: Monoid m => VertexData r m -> 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

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

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

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

Methods

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

show :: VertexData r v -> String #

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

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

Defined in Data.PlaneGraph

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

Defined in Data.PlaneGraph

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 #

fromSimplePolygon Source #

Arguments

:: proxy s 
-> 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 :: (Foldable f, Ord r, Num r) => proxy s -> 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)\)

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

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

Get the number of vertices

>>> numVertices myGraph
4

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

Get the number of Edges

>>> numEdges myGraph
6

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

Get the number of faces

>>> numFaces myGraph
4

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

Get the number of Darts

>>> numDarts myGraph
12

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

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

Enumerate all vertices

>>> vertices' myGraph
[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

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

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.

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

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

faces'' :: (Ord r, Fractional 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

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

The vertex this dart is heading in to

running time: \(O(1)\)

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

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

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

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

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

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

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

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

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

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 order around v.

running time: \(O(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 next dart in the cyclic order around v.

running time: \(O(1)\)

leftFace :: Dart s -> PlaneGraph s v e f r -> FaceId' s 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 -> PlaneGraph s v e f r -> FaceId' s 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)\).

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

Get the next edge along the face

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

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

Get the previous edge along the face

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

boundary :: FaceId' s -> PlaneGraph s v e f r -> 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 -> PlaneGraph s v e f r -> 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 -> 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.

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

gets the id of the outer face

running time: \(O(n)\)

outerFaceDart :: (Ord r, Fractional 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)\)

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

class HasDataOf g i where Source #

Minimal complete definition

dataOf

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

Methods

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

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

\(O(1)\)

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

Reports all edges as line segments

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

Alias for rawFace Boundary

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

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

The polygon describing the face

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

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

Lists all faces of the plane graph.

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 #

ToJSON (VertexId s w) Source # 
Instance details

Defined in Data.PlanarGraph

FromJSON (VertexId s w) Source # 
Instance details

Defined in Data.PlanarGraph

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) :: * 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) :: * 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) :: * 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 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

newtype FaceId s w Source #

A face

Constructors

FaceId 

Fields

Instances
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) :: * 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) :: * 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) :: * 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

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.

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 #

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

Methods

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

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

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 #

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.