{-# Language TemplateHaskell #-}
{-# Language TypeApplications #-}
module Data.Geometry.PointLocation.PersistentSweep
( PointLocationDS(PointLocationDS)
, verticalRayShootingStructure, subdivision, outerFace
, pointLocationDS
, dartAbove, dartAboveOrOn
, faceContaining, faceIdContaining
, InPolygonDS, inPolygonDS
, InOut(..)
, pointInPolygon
, edgeOnOrAbove
) where
import qualified Data.Geometry.VerticalRayShooting.PersistentSweep as VRS
import Control.Lens hiding (contains, below)
import Data.Ext
import Data.Geometry.LineSegment
import Data.Geometry.PlanarSubdivision
import Data.Geometry.Point
import Data.Geometry.Polygon
import qualified Data.List.NonEmpty as NonEmpty
import Data.Proxy
import Data.Util (SP(..))
import qualified Data.Vector as V
data PointLocationDS s v e f r = PointLocationDS {
PointLocationDS s v e f r
-> VerticalRayShootingStructure v (Dart s) r
_verticalRayShootingStructure :: VRS.VerticalRayShootingStructure v (Dart s) r
, PointLocationDS s v e f r -> PlanarSubdivision s v e f r
_subdivision :: PlanarSubdivision s v e f r
, PointLocationDS s v e f r -> FaceId' s
_outerFace :: FaceId' s
} deriving (Int -> PointLocationDS s v e f r -> ShowS
[PointLocationDS s v e f r] -> ShowS
PointLocationDS s v e f r -> String
(Int -> PointLocationDS s v e f r -> ShowS)
-> (PointLocationDS s v e f r -> String)
-> ([PointLocationDS s v e f r] -> ShowS)
-> Show (PointLocationDS s v e f r)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall k (s :: k) v e f r.
(Show r, Show v, Show e, Show f) =>
Int -> PointLocationDS s v e f r -> ShowS
forall k (s :: k) v e f r.
(Show r, Show v, Show e, Show f) =>
[PointLocationDS s v e f r] -> ShowS
forall k (s :: k) v e f r.
(Show r, Show v, Show e, Show f) =>
PointLocationDS s v e f r -> String
showList :: [PointLocationDS s v e f r] -> ShowS
$cshowList :: forall k (s :: k) v e f r.
(Show r, Show v, Show e, Show f) =>
[PointLocationDS s v e f r] -> ShowS
show :: PointLocationDS s v e f r -> String
$cshow :: forall k (s :: k) v e f r.
(Show r, Show v, Show e, Show f) =>
PointLocationDS s v e f r -> String
showsPrec :: Int -> PointLocationDS s v e f r -> ShowS
$cshowsPrec :: forall k (s :: k) v e f r.
(Show r, Show v, Show e, Show f) =>
Int -> PointLocationDS s v e f r -> ShowS
Show,PointLocationDS s v e f r -> PointLocationDS s v e f r -> Bool
(PointLocationDS s v e f r -> PointLocationDS s v e f r -> Bool)
-> (PointLocationDS s v e f r -> PointLocationDS s v e f r -> Bool)
-> Eq (PointLocationDS s v e f r)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall k (s :: k) v e f r.
(Eq r, Eq v, Eq e, Eq f) =>
PointLocationDS s v e f r -> PointLocationDS s v e f r -> Bool
/= :: PointLocationDS s v e f r -> PointLocationDS s v e f r -> Bool
$c/= :: forall k (s :: k) v e f r.
(Eq r, Eq v, Eq e, Eq f) =>
PointLocationDS s v e f r -> PointLocationDS s v e f r -> Bool
== :: PointLocationDS s v e f r -> PointLocationDS s v e f r -> Bool
$c== :: forall k (s :: k) v e f r.
(Eq r, Eq v, Eq e, Eq f) =>
PointLocationDS s v e f r -> PointLocationDS s v e f r -> Bool
Eq)
makeLensesWith (lensRules&generateUpdateableOptics .~ False) ''PointLocationDS
pointLocationDS :: (Ord r, Fractional r)
=> PlanarSubdivision s v e f r -> PointLocationDS s v e f r
pointLocationDS :: PlanarSubdivision s v e f r -> PointLocationDS s v e f r
pointLocationDS PlanarSubdivision s v e f r
ps = VerticalRayShootingStructure v (Dart s) r
-> PlanarSubdivision s v e f r
-> FaceId' s
-> PointLocationDS s v e f r
forall k (s :: k) v e f r.
VerticalRayShootingStructure v (Dart s) r
-> PlanarSubdivision s v e f r
-> FaceId' s
-> PointLocationDS s v e f r
PointLocationDS (NonEmpty (LineSegment 2 v r :+ Dart s)
-> VerticalRayShootingStructure v (Dart s) r
forall r (t :: * -> *) p e.
(Ord r, Fractional r, Foldable1 t) =>
t (LineSegment 2 p r :+ e) -> VerticalRayShootingStructure p e r
VRS.verticalRayShootingStructure NonEmpty (LineSegment 2 v r :+ Dart s)
es) PlanarSubdivision s v e f r
ps (PlanarSubdivision s v e f r -> FaceId' s
forall k (s :: k) v e f r. PlanarSubdivision s v e f r -> FaceId' s
outerFaceId PlanarSubdivision s v e f r
ps)
where
es :: NonEmpty (LineSegment 2 v r :+ Dart s)
es = [LineSegment 2 v r :+ Dart s]
-> NonEmpty (LineSegment 2 v r :+ Dart s)
forall a. [a] -> NonEmpty a
NonEmpty.fromList ([LineSegment 2 v r :+ Dart s]
-> NonEmpty (LineSegment 2 v r :+ Dart s))
-> (PlanarSubdivision s v e f r -> [LineSegment 2 v r :+ Dart s])
-> PlanarSubdivision s v e f r
-> NonEmpty (LineSegment 2 v r :+ Dart s)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Vector (LineSegment 2 v r :+ Dart s)
-> [LineSegment 2 v r :+ Dart s]
forall a. Vector a -> [a]
V.toList (Vector (LineSegment 2 v r :+ Dart s)
-> [LineSegment 2 v r :+ Dart s])
-> (PlanarSubdivision s v e f r
-> Vector (LineSegment 2 v r :+ Dart s))
-> PlanarSubdivision s v e f r
-> [LineSegment 2 v r :+ Dart s]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Dart s, LineSegment 2 v r :+ e) -> LineSegment 2 v r :+ Dart s)
-> Vector (Dart s, LineSegment 2 v r :+ e)
-> Vector (LineSegment 2 v r :+ Dart s)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\(Dart s
d,LineSegment 2 v r :+ e
s) -> LineSegment 2 v r :+ e
s(LineSegment 2 v r :+ e)
-> ((LineSegment 2 v r :+ e) -> LineSegment 2 v r :+ Dart s)
-> LineSegment 2 v r :+ Dart s
forall a b. a -> (a -> b) -> b
&(e -> Identity (Dart s))
-> (LineSegment 2 v r :+ e)
-> Identity (LineSegment 2 v r :+ Dart s)
forall core extra extra'.
Lens (core :+ extra) (core :+ extra') extra extra'
extra ((e -> Identity (Dart s))
-> (LineSegment 2 v r :+ e)
-> Identity (LineSegment 2 v r :+ Dart s))
-> Dart s
-> (LineSegment 2 v r :+ e)
-> LineSegment 2 v r :+ Dart s
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Dart s
d) (Vector (Dart s, LineSegment 2 v r :+ e)
-> Vector (LineSegment 2 v r :+ Dart s))
-> (PlanarSubdivision s v e f r
-> Vector (Dart s, LineSegment 2 v r :+ e))
-> PlanarSubdivision s v e f r
-> Vector (LineSegment 2 v r :+ Dart s)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PlanarSubdivision s v e f r
-> Vector (Dart s, LineSegment 2 v r :+ e)
forall k (s :: k) v e f r.
PlanarSubdivision s v e f r
-> Vector (Dart s, LineSegment 2 v r :+ e)
edgeSegments (PlanarSubdivision s v e f r
-> NonEmpty (LineSegment 2 v r :+ Dart s))
-> PlanarSubdivision s v e f r
-> NonEmpty (LineSegment 2 v r :+ Dart s)
forall a b. (a -> b) -> a -> b
$ PlanarSubdivision s v e f r
ps
dartAbove :: (Ord r, Fractional r)
=> Point 2 r -> PointLocationDS s v e f r -> Maybe (Dart s)
dartAbove :: Point 2 r -> PointLocationDS s v e f r -> Maybe (Dart s)
dartAbove = QueryAlgorithm v (Dart s) r
-> Point 2 r -> PointLocationDS s v e f r -> Maybe (Dart s)
forall k r v (s :: k) e f.
(Ord r, Fractional r) =>
QueryAlgorithm v (Dart s) r
-> Point 2 r -> PointLocationDS s v e f r -> Maybe (Dart s)
queryWith QueryAlgorithm v (Dart s) r
forall r p e.
(Ord r, Num r) =>
Point 2 r
-> VerticalRayShootingStructure p e r
-> Maybe (LineSegment 2 p r :+ e)
VRS.segmentAbove
dartAboveOrOn :: (Ord r, Fractional r)
=> Point 2 r -> PointLocationDS s v e f r -> Maybe (Dart s)
dartAboveOrOn :: Point 2 r -> PointLocationDS s v e f r -> Maybe (Dart s)
dartAboveOrOn = QueryAlgorithm v (Dart s) r
-> Point 2 r -> PointLocationDS s v e f r -> Maybe (Dart s)
forall k r v (s :: k) e f.
(Ord r, Fractional r) =>
QueryAlgorithm v (Dart s) r
-> Point 2 r -> PointLocationDS s v e f r -> Maybe (Dart s)
queryWith QueryAlgorithm v (Dart s) r
forall r p e.
(Ord r, Num r) =>
Point 2 r
-> VerticalRayShootingStructure p e r
-> Maybe (LineSegment 2 p r :+ e)
VRS.segmentAboveOrOn
type QueryAlgorithm v e r =
Point 2 r -> VRS.VerticalRayShootingStructure v e r -> Maybe (LineSegment 2 v r :+ e)
queryWith :: (Ord r, Fractional r)
=> QueryAlgorithm v (Dart s) r
-> Point 2 r -> PointLocationDS s v e f r -> Maybe (Dart s)
queryWith :: QueryAlgorithm v (Dart s) r
-> Point 2 r -> PointLocationDS s v e f r -> Maybe (Dart s)
queryWith QueryAlgorithm v (Dart s) r
query Point 2 r
q = ((LineSegment 2 v r :+ Dart s) -> Dart s)
-> Maybe (LineSegment 2 v r :+ Dart s) -> Maybe (Dart s)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Getting (Dart s) (LineSegment 2 v r :+ Dart s) (Dart s)
-> (LineSegment 2 v r :+ Dart s) -> Dart s
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting (Dart s) (LineSegment 2 v r :+ Dart s) (Dart s)
forall core extra extra'.
Lens (core :+ extra) (core :+ extra') extra extra'
extra) (Maybe (LineSegment 2 v r :+ Dart s) -> Maybe (Dart s))
-> (PointLocationDS s v e f r
-> Maybe (LineSegment 2 v r :+ Dart s))
-> PointLocationDS s v e f r
-> Maybe (Dart s)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. QueryAlgorithm v (Dart s) r
query Point 2 r
q (VerticalRayShootingStructure v (Dart s) r
-> Maybe (LineSegment 2 v r :+ Dart s))
-> (PointLocationDS s v e f r
-> VerticalRayShootingStructure v (Dart s) r)
-> PointLocationDS s v e f r
-> Maybe (LineSegment 2 v r :+ Dart s)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Getting
(VerticalRayShootingStructure v (Dart s) r)
(PointLocationDS s v e f r)
(VerticalRayShootingStructure v (Dart s) r)
-> PointLocationDS s v e f r
-> VerticalRayShootingStructure v (Dart s) r
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting
(VerticalRayShootingStructure v (Dart s) r)
(PointLocationDS s v e f r)
(VerticalRayShootingStructure v (Dart s) r)
forall k (s :: k) v e f r.
Getter
(PointLocationDS s v e f r)
(VerticalRayShootingStructure v (Dart s) r)
verticalRayShootingStructure
faceContaining :: (Ord r, Fractional r)
=> Point 2 r -> PointLocationDS s v e f r -> f
faceContaining :: Point 2 r -> PointLocationDS s v e f r -> f
faceContaining Point 2 r
q PointLocationDS s v e f r
ds = PointLocationDS s v e f r
dsPointLocationDS s v e f r
-> Getting f (PointLocationDS s v e f r) f -> f
forall s a. s -> Getting a s a -> a
^.(PlanarSubdivision s v e f r
-> Const f (PlanarSubdivision s v e f r))
-> PointLocationDS s v e f r -> Const f (PointLocationDS s v e f r)
forall k (s :: k) v e f r.
Getter (PointLocationDS s v e f r) (PlanarSubdivision s v e f r)
subdivision((PlanarSubdivision s v e f r
-> Const f (PlanarSubdivision s v e f r))
-> PointLocationDS s v e f r
-> Const f (PointLocationDS s v e f r))
-> ((f -> Const f f)
-> PlanarSubdivision s v e f r
-> Const f (PlanarSubdivision s v e f r))
-> Getting f (PointLocationDS s v e f r) f
forall b c a. (b -> c) -> (a -> b) -> a -> c
.FaceId' s
-> Lens'
(PlanarSubdivision s v e f r)
(DataOf (PlanarSubdivision s v e f r) (FaceId' s))
forall g i. HasDataOf g i => i -> Lens' g (DataOf g i)
dataOf (Point 2 r -> PointLocationDS s v e f r -> FaceId' s
forall k r (s :: k) v e f.
(Ord r, Fractional r) =>
Point 2 r -> PointLocationDS s v e f r -> FaceId' s
faceIdContaining Point 2 r
q PointLocationDS s v e f r
ds)
faceIdContaining :: (Ord r, Fractional r)
=> Point 2 r -> PointLocationDS s v e f r -> FaceId' s
faceIdContaining :: Point 2 r -> PointLocationDS s v e f r -> FaceId' s
faceIdContaining Point 2 r
q PointLocationDS s v e f r
ds = PointLocationDS s v e f r -> Maybe (Dart s) -> FaceId' s
forall k r (s :: k) v e f.
Ord r =>
PointLocationDS s v e f r -> Maybe (Dart s) -> FaceId' s
dartToFace PointLocationDS s v e f r
ds (Maybe (Dart s) -> FaceId' s) -> Maybe (Dart s) -> FaceId' s
forall a b. (a -> b) -> a -> b
$ Point 2 r -> PointLocationDS s v e f r -> Maybe (Dart s)
forall k r (s :: k) v e f.
(Ord r, Fractional r) =>
Point 2 r -> PointLocationDS s v e f r -> Maybe (Dart s)
dartAbove Point 2 r
q PointLocationDS s v e f r
ds
dartToFace :: Ord r => PointLocationDS s v e f r -> Maybe (Dart s) -> FaceId' s
dartToFace :: PointLocationDS s v e f r -> Maybe (Dart s) -> FaceId' s
dartToFace PointLocationDS s v e f r
ds = FaceId' s -> (Dart s -> FaceId' s) -> Maybe (Dart s) -> FaceId' s
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (PointLocationDS s v e f r
dsPointLocationDS s v e f r
-> Getting (FaceId' s) (PointLocationDS s v e f r) (FaceId' s)
-> FaceId' s
forall s a. s -> Getting a s a -> a
^.Getting (FaceId' s) (PointLocationDS s v e f r) (FaceId' s)
forall k (s :: k) v e f r.
Getter (PointLocationDS s v e f r) (FaceId' s)
outerFace) Dart s -> FaceId' s
getFace
where
ps :: PlanarSubdivision s v e f r
ps = PointLocationDS s v e f r
dsPointLocationDS s v e f r
-> Getting
(PlanarSubdivision s v e f r)
(PointLocationDS s v e f r)
(PlanarSubdivision s v e f r)
-> PlanarSubdivision s v e f r
forall s a. s -> Getting a s a -> a
^.Getting
(PlanarSubdivision s v e f r)
(PointLocationDS s v e f r)
(PlanarSubdivision s v e f r)
forall k (s :: k) v e f r.
Getter (PointLocationDS s v e f r) (PlanarSubdivision s v e f r)
subdivision
getFace :: Dart s -> FaceId' s
getFace Dart s
d = let (Point 2 r
u,Point 2 r
v) = (VertexData r v -> Point 2 r)
-> (VertexData r v -> Point 2 r)
-> (VertexData r v, VertexData r v)
-> (Point 2 r, Point 2 r)
forall (p :: * -> * -> *) a b c d.
Bifunctor p =>
(a -> b) -> (c -> d) -> p a c -> p b d
bimap (VertexData r v
-> Getting (Point 2 r) (VertexData r v) (Point 2 r) -> Point 2 r
forall s a. s -> Getting a s a -> a
^.Getting (Point 2 r) (VertexData r v) (Point 2 r)
forall r1 v r2.
Lens (VertexData r1 v) (VertexData r2 v) (Point 2 r1) (Point 2 r2)
location) (VertexData r v
-> Getting (Point 2 r) (VertexData r v) (Point 2 r) -> Point 2 r
forall s a. s -> Getting a s a -> a
^.Getting (Point 2 r) (VertexData r v) (Point 2 r)
forall r1 v r2.
Lens (VertexData r1 v) (VertexData r2 v) (Point 2 r1) (Point 2 r2)
location) ((VertexData r v, VertexData r v) -> (Point 2 r, Point 2 r))
-> (VertexData r v, VertexData r v) -> (Point 2 r, Point 2 r)
forall a b. (a -> b) -> a -> b
$ Dart s
-> PlanarSubdivision s v e f r -> (VertexData r v, VertexData r v)
forall k (s :: k) v e f r.
Dart s
-> PlanarSubdivision s v e f r -> (VertexData r v, VertexData r v)
endPointData Dart s
d PlanarSubdivision s v e f r
ps
in if Point 2 r
u Point 2 r -> Point 2 r -> Bool
forall a. Ord a => a -> a -> Bool
<= Point 2 r
v then Dart s -> PlanarSubdivision s v e f r -> FaceId' s
forall k (s :: k) v e f r.
Dart s -> PlanarSubdivision s v e f r -> FaceId' s
rightFace Dart s
d PlanarSubdivision s v e f r
ps
else Dart s -> PlanarSubdivision s v e f r -> FaceId' s
forall k (s :: k) v e f r.
Dart s -> PlanarSubdivision s v e f r -> FaceId' s
leftFace Dart s
d PlanarSubdivision s v e f r
ps
data OneOrTwo a = One !a | Two !a !a deriving (Int -> OneOrTwo a -> ShowS
[OneOrTwo a] -> ShowS
OneOrTwo a -> String
(Int -> OneOrTwo a -> ShowS)
-> (OneOrTwo a -> String)
-> ([OneOrTwo a] -> ShowS)
-> Show (OneOrTwo a)
forall a. Show a => Int -> OneOrTwo a -> ShowS
forall a. Show a => [OneOrTwo a] -> ShowS
forall a. Show a => OneOrTwo a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [OneOrTwo a] -> ShowS
$cshowList :: forall a. Show a => [OneOrTwo a] -> ShowS
show :: OneOrTwo a -> String
$cshow :: forall a. Show a => OneOrTwo a -> String
showsPrec :: Int -> OneOrTwo a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> OneOrTwo a -> ShowS
Show,ReadPrec [OneOrTwo a]
ReadPrec (OneOrTwo a)
Int -> ReadS (OneOrTwo a)
ReadS [OneOrTwo a]
(Int -> ReadS (OneOrTwo a))
-> ReadS [OneOrTwo a]
-> ReadPrec (OneOrTwo a)
-> ReadPrec [OneOrTwo a]
-> Read (OneOrTwo a)
forall a. Read a => ReadPrec [OneOrTwo a]
forall a. Read a => ReadPrec (OneOrTwo a)
forall a. Read a => Int -> ReadS (OneOrTwo a)
forall a. Read a => ReadS [OneOrTwo a]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [OneOrTwo a]
$creadListPrec :: forall a. Read a => ReadPrec [OneOrTwo a]
readPrec :: ReadPrec (OneOrTwo a)
$creadPrec :: forall a. Read a => ReadPrec (OneOrTwo a)
readList :: ReadS [OneOrTwo a]
$creadList :: forall a. Read a => ReadS [OneOrTwo a]
readsPrec :: Int -> ReadS (OneOrTwo a)
$creadsPrec :: forall a. Read a => Int -> ReadS (OneOrTwo a)
Read,OneOrTwo a -> OneOrTwo a -> Bool
(OneOrTwo a -> OneOrTwo a -> Bool)
-> (OneOrTwo a -> OneOrTwo a -> Bool) -> Eq (OneOrTwo a)
forall a. Eq a => OneOrTwo a -> OneOrTwo a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OneOrTwo a -> OneOrTwo a -> Bool
$c/= :: forall a. Eq a => OneOrTwo a -> OneOrTwo a -> Bool
== :: OneOrTwo a -> OneOrTwo a -> Bool
$c== :: forall a. Eq a => OneOrTwo a -> OneOrTwo a -> Bool
Eq,Eq (OneOrTwo a)
Eq (OneOrTwo a)
-> (OneOrTwo a -> OneOrTwo a -> Ordering)
-> (OneOrTwo a -> OneOrTwo a -> Bool)
-> (OneOrTwo a -> OneOrTwo a -> Bool)
-> (OneOrTwo a -> OneOrTwo a -> Bool)
-> (OneOrTwo a -> OneOrTwo a -> Bool)
-> (OneOrTwo a -> OneOrTwo a -> OneOrTwo a)
-> (OneOrTwo a -> OneOrTwo a -> OneOrTwo a)
-> Ord (OneOrTwo a)
OneOrTwo a -> OneOrTwo a -> Bool
OneOrTwo a -> OneOrTwo a -> Ordering
OneOrTwo a -> OneOrTwo a -> OneOrTwo a
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall a. Ord a => Eq (OneOrTwo a)
forall a. Ord a => OneOrTwo a -> OneOrTwo a -> Bool
forall a. Ord a => OneOrTwo a -> OneOrTwo a -> Ordering
forall a. Ord a => OneOrTwo a -> OneOrTwo a -> OneOrTwo a
min :: OneOrTwo a -> OneOrTwo a -> OneOrTwo a
$cmin :: forall a. Ord a => OneOrTwo a -> OneOrTwo a -> OneOrTwo a
max :: OneOrTwo a -> OneOrTwo a -> OneOrTwo a
$cmax :: forall a. Ord a => OneOrTwo a -> OneOrTwo a -> OneOrTwo a
>= :: OneOrTwo a -> OneOrTwo a -> Bool
$c>= :: forall a. Ord a => OneOrTwo a -> OneOrTwo a -> Bool
> :: OneOrTwo a -> OneOrTwo a -> Bool
$c> :: forall a. Ord a => OneOrTwo a -> OneOrTwo a -> Bool
<= :: OneOrTwo a -> OneOrTwo a -> Bool
$c<= :: forall a. Ord a => OneOrTwo a -> OneOrTwo a -> Bool
< :: OneOrTwo a -> OneOrTwo a -> Bool
$c< :: forall a. Ord a => OneOrTwo a -> OneOrTwo a -> Bool
compare :: OneOrTwo a -> OneOrTwo a -> Ordering
$ccompare :: forall a. Ord a => OneOrTwo a -> OneOrTwo a -> Ordering
$cp1Ord :: forall a. Ord a => Eq (OneOrTwo a)
Ord,a -> OneOrTwo b -> OneOrTwo a
(a -> b) -> OneOrTwo a -> OneOrTwo b
(forall a b. (a -> b) -> OneOrTwo a -> OneOrTwo b)
-> (forall a b. a -> OneOrTwo b -> OneOrTwo a) -> Functor OneOrTwo
forall a b. a -> OneOrTwo b -> OneOrTwo a
forall a b. (a -> b) -> OneOrTwo a -> OneOrTwo b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> OneOrTwo b -> OneOrTwo a
$c<$ :: forall a b. a -> OneOrTwo b -> OneOrTwo a
fmap :: (a -> b) -> OneOrTwo a -> OneOrTwo b
$cfmap :: forall a b. (a -> b) -> OneOrTwo a -> OneOrTwo b
Functor,OneOrTwo a -> Bool
(a -> m) -> OneOrTwo a -> m
(a -> b -> b) -> b -> OneOrTwo a -> b
(forall m. Monoid m => OneOrTwo m -> m)
-> (forall m a. Monoid m => (a -> m) -> OneOrTwo a -> m)
-> (forall m a. Monoid m => (a -> m) -> OneOrTwo a -> m)
-> (forall a b. (a -> b -> b) -> b -> OneOrTwo a -> b)
-> (forall a b. (a -> b -> b) -> b -> OneOrTwo a -> b)
-> (forall b a. (b -> a -> b) -> b -> OneOrTwo a -> b)
-> (forall b a. (b -> a -> b) -> b -> OneOrTwo a -> b)
-> (forall a. (a -> a -> a) -> OneOrTwo a -> a)
-> (forall a. (a -> a -> a) -> OneOrTwo a -> a)
-> (forall a. OneOrTwo a -> [a])
-> (forall a. OneOrTwo a -> Bool)
-> (forall a. OneOrTwo a -> Int)
-> (forall a. Eq a => a -> OneOrTwo a -> Bool)
-> (forall a. Ord a => OneOrTwo a -> a)
-> (forall a. Ord a => OneOrTwo a -> a)
-> (forall a. Num a => OneOrTwo a -> a)
-> (forall a. Num a => OneOrTwo a -> a)
-> Foldable OneOrTwo
forall a. Eq a => a -> OneOrTwo a -> Bool
forall a. Num a => OneOrTwo a -> a
forall a. Ord a => OneOrTwo a -> a
forall m. Monoid m => OneOrTwo m -> m
forall a. OneOrTwo a -> Bool
forall a. OneOrTwo a -> Int
forall a. OneOrTwo a -> [a]
forall a. (a -> a -> a) -> OneOrTwo a -> a
forall m a. Monoid m => (a -> m) -> OneOrTwo a -> m
forall b a. (b -> a -> b) -> b -> OneOrTwo a -> b
forall a b. (a -> b -> b) -> b -> OneOrTwo a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
product :: OneOrTwo a -> a
$cproduct :: forall a. Num a => OneOrTwo a -> a
sum :: OneOrTwo a -> a
$csum :: forall a. Num a => OneOrTwo a -> a
minimum :: OneOrTwo a -> a
$cminimum :: forall a. Ord a => OneOrTwo a -> a
maximum :: OneOrTwo a -> a
$cmaximum :: forall a. Ord a => OneOrTwo a -> a
elem :: a -> OneOrTwo a -> Bool
$celem :: forall a. Eq a => a -> OneOrTwo a -> Bool
length :: OneOrTwo a -> Int
$clength :: forall a. OneOrTwo a -> Int
null :: OneOrTwo a -> Bool
$cnull :: forall a. OneOrTwo a -> Bool
toList :: OneOrTwo a -> [a]
$ctoList :: forall a. OneOrTwo a -> [a]
foldl1 :: (a -> a -> a) -> OneOrTwo a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> OneOrTwo a -> a
foldr1 :: (a -> a -> a) -> OneOrTwo a -> a
$cfoldr1 :: forall a. (a -> a -> a) -> OneOrTwo a -> a
foldl' :: (b -> a -> b) -> b -> OneOrTwo a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> OneOrTwo a -> b
foldl :: (b -> a -> b) -> b -> OneOrTwo a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> OneOrTwo a -> b
foldr' :: (a -> b -> b) -> b -> OneOrTwo a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> OneOrTwo a -> b
foldr :: (a -> b -> b) -> b -> OneOrTwo a -> b
$cfoldr :: forall a b. (a -> b -> b) -> b -> OneOrTwo a -> b
foldMap' :: (a -> m) -> OneOrTwo a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> OneOrTwo a -> m
foldMap :: (a -> m) -> OneOrTwo a -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> OneOrTwo a -> m
fold :: OneOrTwo m -> m
$cfold :: forall m. Monoid m => OneOrTwo m -> m
Foldable,Functor OneOrTwo
Foldable OneOrTwo
Functor OneOrTwo
-> Foldable OneOrTwo
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> OneOrTwo a -> f (OneOrTwo b))
-> (forall (f :: * -> *) a.
Applicative f =>
OneOrTwo (f a) -> f (OneOrTwo a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> OneOrTwo a -> m (OneOrTwo b))
-> (forall (m :: * -> *) a.
Monad m =>
OneOrTwo (m a) -> m (OneOrTwo a))
-> Traversable OneOrTwo
(a -> f b) -> OneOrTwo a -> f (OneOrTwo b)
forall (t :: * -> *).
Functor t
-> Foldable t
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a. Monad m => OneOrTwo (m a) -> m (OneOrTwo a)
forall (f :: * -> *) a.
Applicative f =>
OneOrTwo (f a) -> f (OneOrTwo a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> OneOrTwo a -> m (OneOrTwo b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> OneOrTwo a -> f (OneOrTwo b)
sequence :: OneOrTwo (m a) -> m (OneOrTwo a)
$csequence :: forall (m :: * -> *) a. Monad m => OneOrTwo (m a) -> m (OneOrTwo a)
mapM :: (a -> m b) -> OneOrTwo a -> m (OneOrTwo b)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> OneOrTwo a -> m (OneOrTwo b)
sequenceA :: OneOrTwo (f a) -> f (OneOrTwo a)
$csequenceA :: forall (f :: * -> *) a.
Applicative f =>
OneOrTwo (f a) -> f (OneOrTwo a)
traverse :: (a -> f b) -> OneOrTwo a -> f (OneOrTwo b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> OneOrTwo a -> f (OneOrTwo b)
$cp2Traversable :: Foldable OneOrTwo
$cp1Traversable :: Functor OneOrTwo
Traversable)
faceIdContaining' :: (Ord r, Fractional r)
=> Point 2 r -> PointLocationDS s v e f r -> OneOrTwo (FaceId' s)
faceIdContaining' :: Point 2 r -> PointLocationDS s v e f r -> OneOrTwo (FaceId' s)
faceIdContaining' Point 2 r
q PointLocationDS s v e f r
ds = OneOrTwo (FaceId' s)
-> (Dart s -> OneOrTwo (FaceId' s))
-> Maybe (Dart s)
-> OneOrTwo (FaceId' s)
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (FaceId' s -> OneOrTwo (FaceId' s)
forall a. a -> OneOrTwo a
One (FaceId' s -> OneOrTwo (FaceId' s))
-> FaceId' s -> OneOrTwo (FaceId' s)
forall a b. (a -> b) -> a -> b
$ PointLocationDS s v e f r
dsPointLocationDS s v e f r
-> Getting (FaceId' s) (PointLocationDS s v e f r) (FaceId' s)
-> FaceId' s
forall s a. s -> Getting a s a -> a
^.Getting (FaceId' s) (PointLocationDS s v e f r) (FaceId' s)
forall k (s :: k) v e f r.
Getter (PointLocationDS s v e f r) (FaceId' s)
outerFace) Dart s -> OneOrTwo (FaceId' s)
getFace (Maybe (Dart s) -> OneOrTwo (FaceId' s))
-> Maybe (Dart s) -> OneOrTwo (FaceId' s)
forall a b. (a -> b) -> a -> b
$ Point 2 r -> PointLocationDS s v e f r -> Maybe (Dart s)
forall k r (s :: k) v e f.
(Ord r, Fractional r) =>
Point 2 r -> PointLocationDS s v e f r -> Maybe (Dart s)
dartAboveOrOn Point 2 r
q PointLocationDS s v e f r
ds
where
ps :: PlanarSubdivision s v e f r
ps = PointLocationDS s v e f r
dsPointLocationDS s v e f r
-> Getting
(PlanarSubdivision s v e f r)
(PointLocationDS s v e f r)
(PlanarSubdivision s v e f r)
-> PlanarSubdivision s v e f r
forall s a. s -> Getting a s a -> a
^.Getting
(PlanarSubdivision s v e f r)
(PointLocationDS s v e f r)
(PlanarSubdivision s v e f r)
forall k (s :: k) v e f r.
Getter (PointLocationDS s v e f r) (PlanarSubdivision s v e f r)
subdivision
getFace :: Dart s -> OneOrTwo (FaceId' s)
getFace = (Dart s, Point 2 r, Point 2 r) -> OneOrTwo (FaceId' s)
getFace' ((Dart s, Point 2 r, Point 2 r) -> OneOrTwo (FaceId' s))
-> (Dart s -> (Dart s, Point 2 r, Point 2 r))
-> Dart s
-> OneOrTwo (FaceId' s)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Dart s -> (Dart s, Point 2 r, Point 2 r)
orient
orient :: Dart s -> (Dart s, Point 2 r, Point 2 r)
orient Dart s
d = let (Point 2 r
u,Point 2 r
v) = (VertexData r v -> Point 2 r)
-> (VertexData r v -> Point 2 r)
-> (VertexData r v, VertexData r v)
-> (Point 2 r, Point 2 r)
forall (p :: * -> * -> *) a b c d.
Bifunctor p =>
(a -> b) -> (c -> d) -> p a c -> p b d
bimap (VertexData r v
-> Getting (Point 2 r) (VertexData r v) (Point 2 r) -> Point 2 r
forall s a. s -> Getting a s a -> a
^.Getting (Point 2 r) (VertexData r v) (Point 2 r)
forall r1 v r2.
Lens (VertexData r1 v) (VertexData r2 v) (Point 2 r1) (Point 2 r2)
location) (VertexData r v
-> Getting (Point 2 r) (VertexData r v) (Point 2 r) -> Point 2 r
forall s a. s -> Getting a s a -> a
^.Getting (Point 2 r) (VertexData r v) (Point 2 r)
forall r1 v r2.
Lens (VertexData r1 v) (VertexData r2 v) (Point 2 r1) (Point 2 r2)
location) ((VertexData r v, VertexData r v) -> (Point 2 r, Point 2 r))
-> (VertexData r v, VertexData r v) -> (Point 2 r, Point 2 r)
forall a b. (a -> b) -> a -> b
$ Dart s
-> PlanarSubdivision s v e f r -> (VertexData r v, VertexData r v)
forall k (s :: k) v e f r.
Dart s
-> PlanarSubdivision s v e f r -> (VertexData r v, VertexData r v)
endPointData Dart s
d PlanarSubdivision s v e f r
ps
in if Point 2 r
u Point 2 r -> Point 2 r -> Bool
forall a. Ord a => a -> a -> Bool
<= Point 2 r
v then (Dart s
d,Point 2 r
u,Point 2 r
v) else (Dart s -> Dart s
forall k (s :: k). Dart s -> Dart s
twin Dart s
d, Point 2 r
v, Point 2 r
u)
getFace' :: (Dart s, Point 2 r, Point 2 r) -> OneOrTwo (FaceId' s)
getFace' (Dart s
d,Point 2 r
u,Point 2 r
v) = case Point 2 r -> Point 2 r -> Point 2 r -> CCW
forall r.
(Ord r, Num r) =>
Point 2 r -> Point 2 r -> Point 2 r -> CCW
ccw Point 2 r
u Point 2 r
q Point 2 r
v of
CCW
CoLinear -> FaceId' s -> FaceId' s -> OneOrTwo (FaceId' s)
forall a. a -> a -> OneOrTwo a
Two (Dart s -> PlanarSubdivision s v e f r -> FaceId' s
forall k (s :: k) v e f r.
Dart s -> PlanarSubdivision s v e f r -> FaceId' s
rightFace Dart s
d PlanarSubdivision s v e f r
ps) (Dart s -> PlanarSubdivision s v e f r -> FaceId' s
forall k (s :: k) v e f r.
Dart s -> PlanarSubdivision s v e f r -> FaceId' s
leftFace Dart s
d PlanarSubdivision s v e f r
ps)
CCW
_ -> FaceId' s -> OneOrTwo (FaceId' s)
forall a. a -> OneOrTwo a
One (Dart s -> PlanarSubdivision s v e f r -> FaceId' s
forall k (s :: k) v e f r.
Dart s -> PlanarSubdivision s v e f r -> FaceId' s
rightFace Dart s
d PlanarSubdivision s v e f r
ps)
data InOut = In | Out deriving (Int -> InOut -> ShowS
[InOut] -> ShowS
InOut -> String
(Int -> InOut -> ShowS)
-> (InOut -> String) -> ([InOut] -> ShowS) -> Show InOut
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [InOut] -> ShowS
$cshowList :: [InOut] -> ShowS
show :: InOut -> String
$cshow :: InOut -> String
showsPrec :: Int -> InOut -> ShowS
$cshowsPrec :: Int -> InOut -> ShowS
Show,InOut -> InOut -> Bool
(InOut -> InOut -> Bool) -> (InOut -> InOut -> Bool) -> Eq InOut
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InOut -> InOut -> Bool
$c/= :: InOut -> InOut -> Bool
== :: InOut -> InOut -> Bool
$c== :: InOut -> InOut -> Bool
Eq)
data Dummy
type InPolygonDS v r = PointLocationDS Dummy (SP Int v) () InOut r
inPolygonDS :: (Fractional r, Ord r) => SimplePolygon v r -> InPolygonDS v r
inPolygonDS :: SimplePolygon v r -> InPolygonDS v r
inPolygonDS SimplePolygon v r
pg = PlanarSubdivision Dummy (SP Int v) () InOut r -> InPolygonDS v r
forall k r (s :: k) v e f.
(Ord r, Fractional r) =>
PlanarSubdivision s v e f r -> PointLocationDS s v e f r
pointLocationDS (PlanarSubdivision Dummy (SP Int v) () InOut r -> InPolygonDS v r)
-> PlanarSubdivision Dummy (SP Int v) () InOut r -> InPolygonDS v r
forall a b. (a -> b) -> a -> b
$ Proxy Dummy
-> SimplePolygon (SP Int v) r
-> InOut
-> InOut
-> PlanarSubdivision Dummy (SP Int v) () InOut r
forall k r (proxy :: k -> *) (s :: k) p f.
(Ord r, Fractional r) =>
proxy s
-> SimplePolygon p r -> f -> f -> PlanarSubdivision s p () f r
fromSimplePolygon (Proxy Dummy
forall k (t :: k). Proxy t
Proxy @Dummy) (SimplePolygon v r -> SimplePolygon (SP Int v) r
forall (t :: PolygonType) p r.
Polygon t p r -> Polygon t (SP Int p) r
numberVertices SimplePolygon v r
pg) InOut
In InOut
Out
edgeOnOrAbove :: (Ord r, Fractional r)
=> Point 2 r -> InPolygonDS v r -> Maybe (LineSegment 2 (SP Int v) r)
edgeOnOrAbove :: Point 2 r -> InPolygonDS v r -> Maybe (LineSegment 2 (SP Int v) r)
edgeOnOrAbove Point 2 r
q InPolygonDS v r
ds = Getting
(LineSegment 2 (SP Int v) r)
(LineSegment 2 (SP Int v) r :+ ())
(LineSegment 2 (SP Int v) r)
-> (LineSegment 2 (SP Int v) r :+ ()) -> LineSegment 2 (SP Int v) r
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting
(LineSegment 2 (SP Int v) r)
(LineSegment 2 (SP Int v) r :+ ())
(LineSegment 2 (SP Int v) r)
forall core extra core'.
Lens (core :+ extra) (core' :+ extra) core core'
core ((LineSegment 2 (SP Int v) r :+ ()) -> LineSegment 2 (SP Int v) r)
-> (Dart Dummy -> LineSegment 2 (SP Int v) r :+ ())
-> Dart Dummy
-> LineSegment 2 (SP Int v) r
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Dart Dummy
-> PlanarSubdivision Dummy (SP Int v) () InOut r
-> LineSegment 2 (SP Int v) r :+ ())
-> PlanarSubdivision Dummy (SP Int v) () InOut r
-> Dart Dummy
-> LineSegment 2 (SP Int v) r :+ ()
forall a b c. (a -> b -> c) -> b -> a -> c
flip Dart Dummy
-> PlanarSubdivision Dummy (SP Int v) () InOut r
-> LineSegment 2 (SP Int v) r :+ ()
forall k (s :: k) v e f r.
Dart s -> PlanarSubdivision s v e f r -> LineSegment 2 v r :+ e
edgeSegment (InPolygonDS v r
dsInPolygonDS v r
-> Getting
(PlanarSubdivision Dummy (SP Int v) () InOut r)
(InPolygonDS v r)
(PlanarSubdivision Dummy (SP Int v) () InOut r)
-> PlanarSubdivision Dummy (SP Int v) () InOut r
forall s a. s -> Getting a s a -> a
^.Getting
(PlanarSubdivision Dummy (SP Int v) () InOut r)
(InPolygonDS v r)
(PlanarSubdivision Dummy (SP Int v) () InOut r)
forall k (s :: k) v e f r.
Getter (PointLocationDS s v e f r) (PlanarSubdivision s v e f r)
subdivision) (Dart Dummy -> LineSegment 2 (SP Int v) r)
-> Maybe (Dart Dummy) -> Maybe (LineSegment 2 (SP Int v) r)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Point 2 r -> InPolygonDS v r -> Maybe (Dart Dummy)
forall k r (s :: k) v e f.
(Ord r, Fractional r) =>
Point 2 r -> PointLocationDS s v e f r -> Maybe (Dart s)
dartAboveOrOn Point 2 r
q InPolygonDS v r
ds
pointInPolygon :: (Ord r, Fractional r) => Point 2 r -> InPolygonDS v r -> InOut
pointInPolygon :: Point 2 r -> InPolygonDS v r -> InOut
pointInPolygon Point 2 r
q InPolygonDS v r
ds = case Point 2 r -> InPolygonDS v r -> OneOrTwo (FaceId' Dummy)
forall k r (s :: k) v e f.
(Ord r, Fractional r) =>
Point 2 r -> PointLocationDS s v e f r -> OneOrTwo (FaceId' s)
faceIdContaining' Point 2 r
q InPolygonDS v r
ds of
One FaceId' Dummy
i -> InPolygonDS v r
dsInPolygonDS v r -> Getting InOut (InPolygonDS v r) InOut -> InOut
forall s a. s -> Getting a s a -> a
^.(PlanarSubdivision Dummy (SP Int v) () InOut r
-> Const InOut (PlanarSubdivision Dummy (SP Int v) () InOut r))
-> InPolygonDS v r -> Const InOut (InPolygonDS v r)
forall k (s :: k) v e f r.
Getter (PointLocationDS s v e f r) (PlanarSubdivision s v e f r)
subdivision((PlanarSubdivision Dummy (SP Int v) () InOut r
-> Const InOut (PlanarSubdivision Dummy (SP Int v) () InOut r))
-> InPolygonDS v r -> Const InOut (InPolygonDS v r))
-> ((InOut -> Const InOut InOut)
-> PlanarSubdivision Dummy (SP Int v) () InOut r
-> Const InOut (PlanarSubdivision Dummy (SP Int v) () InOut r))
-> Getting InOut (InPolygonDS v r) InOut
forall b c a. (b -> c) -> (a -> b) -> a -> c
.FaceId' Dummy
-> Lens'
(PlanarSubdivision Dummy (SP Int v) () InOut r)
(DataOf
(PlanarSubdivision Dummy (SP Int v) () InOut r) (FaceId' Dummy))
forall g i. HasDataOf g i => i -> Lens' g (DataOf g i)
dataOf FaceId' Dummy
i
Two FaceId' Dummy
_ FaceId' Dummy
_ -> InOut
In