module Data.Geometry.Point where
import Control.DeepSeq
import Control.Lens
import qualified Data.CircularList as C
import qualified Data.CircularList.Util as CU
import Data.Ext
import qualified Data.Foldable as F
import Data.Geometry.Properties
import Data.Geometry.Vector
import qualified Data.Geometry.Vector as Vec
import qualified Data.List as L
import Data.Proxy
import qualified Data.Traversable as T
import qualified Data.Vector.Fixed as FV
import GHC.Generics (Generic)
import GHC.TypeLits
newtype Point d r = Point { toVec :: Vector d r } deriving (Generic)
instance (Show r, Arity d) => Show (Point d r) where
show (Point (Vector v)) = mconcat [ "Point", show $ FV.length v , " "
, show $ F.toList v
]
deriving instance (Eq r, Arity d) => Eq (Point d r)
deriving instance (Ord r, Arity d) => Ord (Point d r)
deriving instance Arity d => Functor (Point d)
deriving instance Arity d => F.Foldable (Point d)
deriving instance Arity d => T.Traversable (Point d)
deriving instance (Arity d, NFData r) => NFData (Point d r)
type instance NumType (Point d r) = r
type instance Dimension (Point d r) = d
instance Arity d => Affine (Point d) where
type Diff (Point d) = Vector d
p .-. q = toVec p ^-^ toVec q
p .+^ v = Point $ toVec p ^+^ v
origin :: (Arity d, Num r) => Point d r
origin = Point $ pure 0
vector :: Lens' (Point d r) (Vector d r)
vector = lens toVec (const Point)
unsafeCoord :: Arity d => Int -> Lens' (Point d r) r
unsafeCoord i = vector . FV.element (i1)
coord :: forall proxy i d r. (Index' (i1) d, Arity d) => proxy i -> Lens' (Point d r) r
coord _ = vector . Vec.element (Proxy :: Proxy (i1))
pointFromList :: Arity d => [r] -> Maybe (Point d r)
pointFromList = fmap Point . Vec.vectorFromList
pattern Point2 :: r -> r -> Point 2 r
pattern Point2 x y <- (_point2 -> (x,y))
where
Point2 x y = point2 x y
pattern Point3 :: r -> r -> r -> Point 3 r
pattern Point3 x y z <- (_point3 -> (x,y,z))
where
Point3 x y z = point3 x y z
point2 :: r -> r -> Point 2 r
point2 x y = Point $ v2 x y
_point2 :: Point 2 r -> (r,r)
_point2 p = (p^.xCoord, p^.yCoord)
point3 :: r -> r -> r -> Point 3 r
point3 x y z = Point $ v3 x y z
_point3 :: Point 3 r -> (r,r,r)
_point3 p = (p^.xCoord, p^.yCoord, p^.zCoord)
type i <=. d = (Index' (i1) d, Arity d)
xCoord :: (1 <=. d) => Lens' (Point d r) r
xCoord = coord (C :: C 1)
yCoord :: (2 <=. d) => Lens' (Point d r) r
yCoord = coord (C :: C 2)
zCoord :: (3 <=. d) => Lens' (Point d r) r
zCoord = coord (C :: C 3)
class PointFunctor g where
pmap :: (Point (Dimension (g r)) r -> Point (Dimension (g s)) s) -> g r -> g s
instance PointFunctor (Point d) where
pmap f = f
data CCW = CCW | CoLinear | CW
deriving (Show,Eq)
ccw :: (Ord r, Num r) => Point 2 r -> Point 2 r -> Point 2 r -> CCW
ccw p q r = case z `compare` 0 of
LT -> CW
GT -> CCW
EQ -> CoLinear
where
Vector2 ux uy = q .-. p
Vector2 vx vy = r .-. p
z = ux * vy uy * vx
sortArround :: (Ord r, Num r)
=> Point 2 r :+ q -> [Point 2 r :+ p] -> [Point 2 r :+ p]
sortArround c = L.sortBy (ccwCmpAround c)
data Quadrant = TopRight | TopLeft | BottomLeft | BottomRight
deriving (Show,Read,Eq,Ord,Enum,Bounded)
quadrantWith :: (Ord r, 1 <=. d, 2 <=. d)
=> Point d r :+ q -> Point d r :+ p -> Quadrant
quadrantWith (c :+ _) (p :+ _) = case ( (c^.xCoord) `compare` (p^.xCoord)
, (c^.yCoord) `compare` (p^.yCoord) ) of
(EQ, EQ) -> TopRight
(LT, EQ) -> TopRight
(LT, LT) -> TopRight
(EQ, LT) -> TopLeft
(GT, LT) -> TopLeft
(GT, EQ) -> BottomLeft
(GT, GT) -> BottomLeft
(EQ, GT) -> BottomRight
(LT, GT) -> BottomRight
quadrant :: (Ord r, Num r, 1 <=. d, 2 <=. d) => Point d r :+ p -> Quadrant
quadrant = quadrantWith (ext origin)
partitionIntoQuadrants :: (Ord r, 1 <=. d, 2 <=. d)
=> Point d r :+ q
-> [Point d r :+ p]
-> ( [Point d r :+ p], [Point d r :+ p]
, [Point d r :+ p], [Point d r :+ p]
)
partitionIntoQuadrants c pts = (topL, topR, bottomL, bottomR)
where
(below',above') = L.partition (on yCoord) pts
(bottomL,bottomR) = L.partition (on xCoord) below'
(topL,topR) = L.partition (on xCoord) above'
on l q = q^.core.l < c^.core.l
ccwCmpAround :: (Num r, Ord r)
=> Point 2 r :+ qc -> Point 2 r :+ p -> Point 2 r :+ q -> Ordering
ccwCmpAround c q r = case (quadrantWith c q `compare` quadrantWith c r) of
EQ -> case ccw (c^.core) (q^.core) (r^.core) of
CCW -> LT
CW -> GT
CoLinear -> qdA (c^.core) (q^.core)
`compare`
qdA (c^.core) (r^.core)
x -> x
cwCmpAround :: (Num r, Ord r)
=> Point 2 r :+ qc -> Point 2 r :+ p -> Point 2 r :+ q -> Ordering
cwCmpAround c q r = case (quadrantWith c q `compare` quadrantWith c r) of
EQ -> case ccw (c^.core) (q^.core) (r^.core) of
CCW -> GT
CW -> LT
CoLinear -> qdA (c^.core) (q^.core)
`compare`
qdA (c^.core) (r^.core)
LT -> GT
GT -> LT
insertIntoCyclicOrder :: (Ord r, Num r)
=> Point 2 r :+ q -> Point 2 r :+ p
-> C.CList (Point 2 r :+ p) -> C.CList (Point 2 r :+ p)
insertIntoCyclicOrder c = CU.insertOrdBy (ccwCmpAround c)
squaredEuclideanDist :: (Num r, Arity d) => Point d r -> Point d r -> r
squaredEuclideanDist = qdA
euclideanDist :: (Floating r, Arity d) => Point d r -> Point d r -> r
euclideanDist = distanceA