module Data.PlanarGraph.Dual where
import Control.Lens hiding ((.=))
import Data.PlanarGraph.Core
import Data.PlanarGraph.Dart
import qualified Data.Vector as V
import Data.Maybe (fromMaybe)
faces' :: PlanarGraph s w v e f -> V.Vector (FaceId s w)
faces' :: PlanarGraph s w v e f -> Vector (FaceId s w)
faces' = (VertexId s (DualOf w) -> FaceId s w)
-> Vector (VertexId s (DualOf w)) -> Vector (FaceId s w)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap VertexId s (DualOf w) -> FaceId s w
forall k (s :: k) (w :: World). VertexId s (DualOf w) -> FaceId s w
FaceId (Vector (VertexId s (DualOf w)) -> Vector (FaceId s w))
-> (PlanarGraph s w v e f -> Vector (VertexId s (DualOf w)))
-> PlanarGraph s w v e f
-> Vector (FaceId s w)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PlanarGraph s (DualOf w) f e v -> Vector (VertexId s (DualOf w))
forall k (s :: k) (w :: World) v e f.
PlanarGraph s w v e f -> Vector (VertexId s w)
vertices' (PlanarGraph s (DualOf w) f e v -> Vector (VertexId s (DualOf w)))
-> (PlanarGraph s w v e f -> PlanarGraph s (DualOf w) f e v)
-> PlanarGraph s w v e f
-> Vector (VertexId s (DualOf w))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PlanarGraph s w v e f -> PlanarGraph s (DualOf w) f e v
forall k (s :: k) (w :: World) v e f.
PlanarGraph s w v e f -> PlanarGraph s (DualOf w) f e v
_dual
faces :: PlanarGraph s w v e f -> V.Vector (FaceId s w, f)
faces :: PlanarGraph s w v e f -> Vector (FaceId s w, f)
faces PlanarGraph s w v e f
g = Vector (FaceId s w) -> Vector f -> Vector (FaceId s w, f)
forall a b. Vector a -> Vector b -> Vector (a, b)
V.zip (PlanarGraph s w v e f -> Vector (FaceId s w)
forall k (s :: k) (w :: World) v e f.
PlanarGraph s w v e f -> Vector (FaceId s w)
faces' PlanarGraph s w v e f
g) (PlanarGraph s w v e f
gPlanarGraph s w v e f
-> Getting (Vector f) (PlanarGraph s w v e f) (Vector f)
-> Vector f
forall s a. s -> Getting a s a -> a
^.Getting (Vector f) (PlanarGraph s w v e f) (Vector f)
forall k (s :: k) (w :: World) v e f f'.
Lens
(PlanarGraph s w v e f)
(PlanarGraph s w v e f')
(Vector f)
(Vector f')
faceData)
leftFace :: Dart s -> PlanarGraph s w v e f -> FaceId s w
leftFace :: Dart s -> PlanarGraph s w v e f -> FaceId s w
leftFace Dart s
d PlanarGraph s w v e f
g = VertexId s (DualOf w) -> FaceId s w
forall k (s :: k) (w :: World). VertexId s (DualOf w) -> FaceId s w
FaceId (VertexId s (DualOf w) -> FaceId s w)
-> (PlanarGraph s (DualOf w) f e v -> VertexId s (DualOf w))
-> PlanarGraph s (DualOf w) f e v
-> FaceId s w
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Dart s -> PlanarGraph s (DualOf w) f e v -> VertexId s (DualOf w)
forall k (s :: k) (w :: World) v e f.
Dart s -> PlanarGraph s w v e f -> VertexId s w
headOf Dart s
d (PlanarGraph s (DualOf w) f e v -> FaceId s w)
-> PlanarGraph s (DualOf w) f e v -> FaceId s w
forall a b. (a -> b) -> a -> b
$ PlanarGraph s w v e f -> PlanarGraph s (DualOf w) f e v
forall k (s :: k) (w :: World) v e f.
PlanarGraph s w v e f -> PlanarGraph s (DualOf w) f e v
_dual PlanarGraph s w v e f
g
rightFace :: Dart s -> PlanarGraph s w v e f -> FaceId s w
rightFace :: Dart s -> PlanarGraph s w v e f -> FaceId s w
rightFace Dart s
d PlanarGraph s w v e f
g = VertexId s (DualOf w) -> FaceId s w
forall k (s :: k) (w :: World). VertexId s (DualOf w) -> FaceId s w
FaceId (VertexId s (DualOf w) -> FaceId s w)
-> (PlanarGraph s (DualOf w) f e v -> VertexId s (DualOf w))
-> PlanarGraph s (DualOf w) f e v
-> FaceId s w
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Dart s -> PlanarGraph s (DualOf w) f e v -> VertexId s (DualOf w)
forall k (s :: k) (w :: World) v e f.
Dart s -> PlanarGraph s w v e f -> VertexId s w
tailOf Dart s
d (PlanarGraph s (DualOf w) f e v -> FaceId s w)
-> PlanarGraph s (DualOf w) f e v -> FaceId s w
forall a b. (a -> b) -> a -> b
$ PlanarGraph s w v e f -> PlanarGraph s (DualOf w) f e v
forall k (s :: k) (w :: World) v e f.
PlanarGraph s w v e f -> PlanarGraph s (DualOf w) f e v
_dual PlanarGraph s w v e f
g
nextEdge :: Dart s -> PlanarGraph s w v e f -> Dart s
nextEdge :: Dart s -> PlanarGraph s w v e f -> Dart s
nextEdge Dart s
d = Dart s -> PlanarGraph s (DualOf w) f e v -> Dart s
forall k (s :: k) (w :: World) v e f.
Dart s -> PlanarGraph s w v e f -> Dart s
nextIncidentEdge Dart s
d (PlanarGraph s (DualOf w) f e v -> Dart s)
-> (PlanarGraph s w v e f -> PlanarGraph s (DualOf w) f e v)
-> PlanarGraph s w v e f
-> Dart s
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PlanarGraph s w v e f -> PlanarGraph s (DualOf w) f e v
forall k (s :: k) (w :: World) v e f.
PlanarGraph s w v e f -> PlanarGraph s (DualOf w) f e v
_dual
prevEdge :: Dart s -> PlanarGraph s w v e f -> Dart s
prevEdge :: Dart s -> PlanarGraph s w v e f -> Dart s
prevEdge Dart s
d = Dart s -> PlanarGraph s (DualOf w) f e v -> Dart s
forall k (s :: k) (w :: World) v e f.
Dart s -> PlanarGraph s w v e f -> Dart s
prevIncidentEdge Dart s
d (PlanarGraph s (DualOf w) f e v -> Dart s)
-> (PlanarGraph s w v e f -> PlanarGraph s (DualOf w) f e v)
-> PlanarGraph s w v e f
-> Dart s
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PlanarGraph s w v e f -> PlanarGraph s (DualOf w) f e v
forall k (s :: k) (w :: World) v e f.
PlanarGraph s w v e f -> PlanarGraph s (DualOf w) f e v
_dual
boundaryDart :: FaceId s w -> PlanarGraph s w v e f -> Dart s
boundaryDart :: FaceId s w -> PlanarGraph s w v e f -> Dart s
boundaryDart FaceId s w
f = Vector (Dart s) -> Dart s
forall a. Vector a -> a
V.head (Vector (Dart s) -> Dart s)
-> (PlanarGraph s w v e f -> Vector (Dart s))
-> PlanarGraph s w v e f
-> Dart s
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FaceId s w -> PlanarGraph s w v e f -> Vector (Dart s)
forall k (s :: k) (w :: World) v e f.
FaceId s w -> PlanarGraph s w v e f -> Vector (Dart s)
boundary FaceId s w
f
boundary :: FaceId s w -> PlanarGraph s w v e f -> V.Vector (Dart s)
boundary :: FaceId s w -> PlanarGraph s w v e f -> Vector (Dart s)
boundary (FaceId VertexId s (DualOf w)
v) PlanarGraph s w v e f
g = VertexId s (DualOf w)
-> PlanarGraph s (DualOf w) f e v -> Vector (Dart s)
forall k (s :: k) (w :: World) v e f.
VertexId s w -> PlanarGraph s w v e f -> Vector (Dart s)
incidentEdges VertexId s (DualOf w)
v (PlanarGraph s (DualOf w) f e v -> Vector (Dart s))
-> PlanarGraph s (DualOf w) f e v -> Vector (Dart s)
forall a b. (a -> b) -> a -> b
$ PlanarGraph s w v e f -> PlanarGraph s (DualOf w) f e v
forall k (s :: k) (w :: World) v e f.
PlanarGraph s w v e f -> PlanarGraph s (DualOf w) f e v
_dual PlanarGraph s w v e f
g
boundary' :: Dart s -> PlanarGraph s w v e f -> V.Vector (Dart s)
boundary' :: Dart s -> PlanarGraph s w v e f -> Vector (Dart s)
boundary' Dart s
d PlanarGraph s w v e f
g = Vector (Dart s) -> Maybe (Vector (Dart s)) -> Vector (Dart s)
forall a. a -> Maybe a -> a
fromMaybe ([Char] -> Vector (Dart s)
forall a. HasCallStack => [Char] -> a
error [Char]
"boundary'") (Maybe (Vector (Dart s)) -> Vector (Dart s))
-> (Vector (Dart s) -> Maybe (Vector (Dart s)))
-> Vector (Dart s)
-> Vector (Dart s)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Dart s -> Vector (Dart s) -> Maybe (Vector (Dart s))
forall a. Eq a => a -> Vector a -> Maybe (Vector a)
rotateTo Dart s
d (Vector (Dart s) -> Vector (Dart s))
-> Vector (Dart s) -> Vector (Dart s)
forall a b. (a -> b) -> a -> b
$ FaceId s w -> PlanarGraph s w v e f -> Vector (Dart s)
forall k (s :: k) (w :: World) v e f.
FaceId s w -> PlanarGraph s w v e f -> Vector (Dart s)
boundary (Dart s -> PlanarGraph s w v e f -> FaceId s w
forall k (s :: k) (w :: World) v e f.
Dart s -> PlanarGraph s w v e f -> FaceId s w
rightFace Dart s
d PlanarGraph s w v e f
g) PlanarGraph s w v e f
g
where
rotateTo :: Eq a => a -> V.Vector a -> Maybe (V.Vector a)
rotateTo :: a -> Vector a -> Maybe (Vector a)
rotateTo a
x Vector a
v = Int -> Vector a
f (Int -> Vector a) -> Maybe Int -> Maybe (Vector a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> Vector a -> Maybe Int
forall a. Eq a => a -> Vector a -> Maybe Int
V.elemIndex a
x Vector a
v
where
f :: Int -> Vector a
f Int
i = let (Vector a
a,Vector a
b) = Int -> Vector a -> (Vector a, Vector a)
forall a. Int -> Vector a -> (Vector a, Vector a)
V.splitAt Int
i Vector a
v in Vector a
b Vector a -> Vector a -> Vector a
forall a. Semigroup a => a -> a -> a
<> Vector a
a
boundaryVertices :: FaceId s w -> PlanarGraph s w v e f -> V.Vector (VertexId s w)
boundaryVertices :: FaceId s w -> PlanarGraph s w v e f -> Vector (VertexId s w)
boundaryVertices FaceId s w
f PlanarGraph s w v e f
g = (Dart s -> PlanarGraph s w v e f -> VertexId s w)
-> PlanarGraph s w v e f -> Dart s -> VertexId s w
forall a b c. (a -> b -> c) -> b -> a -> c
flip Dart s -> PlanarGraph s w v e f -> VertexId s w
forall k (s :: k) (w :: World) v e f.
Dart s -> PlanarGraph s w v e f -> VertexId s w
tailOf PlanarGraph s w v e f
g (Dart s -> VertexId s w)
-> Vector (Dart s) -> Vector (VertexId s w)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> FaceId s w -> PlanarGraph s w v e f -> Vector (Dart s)
forall k (s :: k) (w :: World) v e f.
FaceId s w -> PlanarGraph s w v e f -> Vector (Dart s)
boundary FaceId s w
f PlanarGraph s w v e f
g