hgeometry-0.9.0.0: 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

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

(FromJSON v, FromJSON e, FromJSON f, FromJSON r) => FromJSON (PlaneGraph s v e f r) 
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]

(ToJSON v, ToJSON e, ToJSON f, ToJSON r) => ToJSON (PlaneGraph s v e f r) 
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

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

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

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

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.9.0.0-inplace" 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 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 :: k) (w :: World) v e f :: forall k. k -> World -> Type -> Type -> Type -> Type #

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

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

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

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.9.0.0-inplace" 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
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 #

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 #

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

Defined in Data.PlaneGraph.Core

Methods

parseJSON :: Value -> Parser (VertexData r v)

parseJSONList :: Value -> Parser [VertexData r v]

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

Defined in Data.PlaneGraph.Core

Methods

toJSON :: VertexData r v -> Value

toEncoding :: VertexData r v -> Encoding

toJSONList :: [VertexData r v] -> Value

toEncodingList :: [VertexData r v] -> Encoding

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.9.0.0-inplace" 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 #

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

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

Transforms the planar graph into a format taht can be easily converted into JSON format. 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 :: proxy s -> Gr (Vtx v e r) (Face f) -> PlaneGraph s v e f r Source #

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

Get the number of vertices

>>> numVertices smallG
4

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

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

Get the number of Darts

>>> numDarts smallG
10

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

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

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

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 :: Dart s -> Dart s #

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]

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.

>>> incomingEdges (VertexId 1) smallG
[Dart (Arc 1) -1]

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.

>>> outgoingEdges (VertexId 1) smallG
[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]

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 in clockwise direction.

running time: \(O(1)\)

>>> nextIncidentEdge (dart 1 "+1") smallG
Dart (Arc 2) +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 (in clockwise order)

running time: \(O(1)\)

>>> prevIncidentEdge (dart 1 "+1") smallG
Dart (Arc 0) +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, 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

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.

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

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

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

class HasDataOf g i where #

Associated Types

type DataOf g i :: Type #

Methods

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

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

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

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

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

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

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

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

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

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

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,LineSegment (Closed (Point2 [0,0] :+ 0)) (Closed (Point2 [2,0] :+ 2)) :+ "0->2")
(Dart (Arc 1) +1,LineSegment (Closed (Point2 [0,0] :+ 0)) (Closed (Point2 [2,2] :+ 1)) :+ "0->1")
(Dart (Arc 2) +1,LineSegment (Closed (Point2 [0,0] :+ 0)) (Closed (Point2 [-1,4] :+ 3)) :+ "0->3")
(Dart (Arc 4) +1,LineSegment (Closed (Point2 [2,2] :+ 1)) (Closed (Point2 [2,0] :+ 2)) :+ "1->2")
(Dart (Arc 3) +1,LineSegment (Closed (Point2 [2,2] :+ 1)) (Closed (Point2 [-1,4] :+ 3)) :+ "1->3")

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 :: k) (w :: World) :: forall k. k -> World -> Type #

Constructors

VertexId 

Fields

Instances
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 #

NFData (VertexId s w) 
Instance details

Defined in Data.PlanarGraph.Core

Methods

rnf :: VertexId s w -> () #

FromJSON (VertexId s w) 
Instance details

Defined in Data.PlanarGraph.Core

Methods

parseJSON :: Value -> Parser (VertexId s w)

parseJSONList :: Value -> Parser [VertexId s w]

ToJSON (VertexId s w) 
Instance details

Defined in Data.PlanarGraph.Core

Methods

toJSON :: VertexId s w -> Value

toEncoding :: VertexId s w -> Encoding

toJSONList :: [VertexId s w] -> Value

toEncodingList :: [VertexId s w] -> Encoding

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

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

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

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.9.0.0-inplace" 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) :: forall k. k -> World -> Type #

Constructors

FaceId 

Fields

Instances
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 #

FromJSON (FaceId s w) 
Instance details

Defined in Data.PlanarGraph.Core

Methods

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

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

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

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

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

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

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) :: forall k. k -> Type #

Instances
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 #

NFData (Dart s) 
Instance details

Defined in Data.PlanarGraph.Dart

Methods

rnf :: Dart s -> () #

Arbitrary (Dart s) 
Instance details

Defined in Data.PlanarGraph.Dart

Methods

arbitrary :: Gen (Dart s)

shrink :: Dart s -> [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) :: Type #

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

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

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.9.0.0-inplace" False) (C1 (MetaCons "Dart" PrefixI True) (S1 (MetaSel (Just "_arc") NoSourceUnpackedness SourceStrict DecidedUnpack) (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 #

Constructors

Primal 
Dual 
Instances
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 #

type FaceId' (s :: k) = FaceId s 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 :: (FromJSON v, FromJSON e, FromJSON f, FromJSON r) => proxy s -> ByteString -> Either ParseException (PlaneGraph s v e f r) Source #

Reads a plane graph from a bytestring