{-# LANGUAGE ScopedTypeVariables  #-}
{-# LANGUAGE UndecidableInstances #-}
module Data.Geometry.Point( Point(..)
                          , origin, vector
                          , pointFromList
                          , coord , unsafeCoord
                          , projectPoint
                          , pattern Point2
                          , pattern Point3
                          , xCoord, yCoord, zCoord
                          , PointFunctor(..)
                          , CCW(..), ccw, ccw'
                          , ccwCmpAround, cwCmpAround, ccwCmpAroundWith, cwCmpAroundWith
                          , sortAround, insertIntoCyclicOrder
                          , Quadrant(..), quadrantWith, quadrant, partitionIntoQuadrants
                          , cmpByDistanceTo
                          , squaredEuclideanDist, euclideanDist
                          ) where
import           Control.DeepSeq
import           Control.Lens
import           Data.Aeson
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.Ord (comparing)
import           Data.Proxy
import           GHC.Generics (Generic)
import           GHC.TypeLits
import           Test.QuickCheck (Arbitrary)
import           Text.ParserCombinators.ReadP (ReadP, string,pfail)
import           Text.ParserCombinators.ReadPrec (lift)
import           Text.Read (Read(..),readListPrecDefault, readPrec_to_P,minPrec)
newtype Point d r = Point { toVec :: Vector d r } deriving (Generic)
instance (Show r, Arity d) => Show (Point d r) where
  show (Point v) = mconcat [ "Point", show $ F.length v , " "
                           , show $ F.toList v
                           ]
instance (Read r, Arity d) => Read (Point d r) where
  readPrec     = lift readPt
  readListPrec = readListPrecDefault
readPt :: forall d r. (Arity d, Read r) => ReadP (Point d r)
readPt = do let d = natVal (Proxy :: Proxy d)
            _  <- string $ "Point" <> show d <> " "
            rs <- readPrec_to_P readPrec minPrec
            case pointFromList rs of
              Just p -> pure p
              _      -> pfail
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                => Foldable (Point d)
deriving instance Arity d                => Traversable (Point d)
deriving instance (Arity d, NFData r)    => NFData (Point d r)
deriving instance (Arity d, Arbitrary r) => Arbitrary (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
instance (FromJSON r, Arity d, KnownNat d) => FromJSON (Point d r) where
  parseJSON = fmap Point . parseJSON
instance (ToJSON r, Arity d) => ToJSON (Point d r) where
  toJSON     = toJSON     . toVec
  toEncoding = toEncoding . toVec
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 . singular (ix (i-1))
                
coord   :: forall proxy i d r. (1 <= i, i <= d, ((i - 1) + 1) ~ i
                               , Arity (i - 1), Arity d
                               ) => proxy i -> Lens' (Point d r) r
coord _ = vector . Vec.element (Proxy :: Proxy (i-1))
{-# INLINABLE coord #-}
pointFromList :: Arity d => [r] -> Maybe (Point d r)
pointFromList = fmap Point . Vec.vectorFromList
projectPoint :: (Arity i, Arity d, i <= d) => Point d r -> Point i r
projectPoint = Point . prefix . toVec
pattern Point2       :: r -> r -> Point 2 r
pattern Point2 x y = Point (Vector2 x y)
{-# COMPLETE Point2 #-}
pattern Point3       :: r -> r -> r -> Point 3 r
pattern Point3 x y z = (Point (Vector3 x y z))
{-# COMPLETE Point3 #-}
xCoord :: (1 <= d, Arity d) => Lens' (Point d r) r
xCoord = coord (C :: C 1)
{-# INLINABLE xCoord #-}
yCoord :: (2 <= d, Arity d) => Lens' (Point d r) r
yCoord = coord (C :: C 2)
{-# INLINABLE yCoord #-}
zCoord :: (3 <= d, Arity d) => Lens' (Point d r) r
zCoord = coord (C :: C 3)
{-# INLINABLE zCoord #-}
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
ccw' :: (Ord r, Num r) => Point 2 r :+ a -> Point 2 r :+ b -> Point 2 r :+ c -> CCW
ccw' p q r = ccw (p^.core) (q^.core) (r^.core)
sortAround   :: (Ord r, Num r)
             => Point 2 r :+ q -> [Point 2 r :+ p] -> [Point 2 r :+ p]
sortAround c = L.sortBy (ccwCmpAround c <> cmpByDistanceTo c)
data Quadrant = TopRight | TopLeft | BottomLeft | BottomRight
              deriving (Show,Read,Eq,Ord,Enum,Bounded)
quadrantWith                   :: (Ord r, 1 <= d, 2 <= d, Arity 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, Arity d) => Point d r :+ p -> Quadrant
quadrant = quadrantWith (ext origin)
partitionIntoQuadrants       :: (Ord r, 1 <= d, 2 <= d, Arity 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
ccwCmpAroundWith                              :: (Ord r, Num r)
                                              => Vector 2 r
                                              -> Point 2 r :+ c
                                              -> Point 2 r :+ a -> Point 2 r :+ b
                                              -> Ordering
ccwCmpAroundWith z@(Vector2 zx zy) (c :+ _) (q :+ _) (r :+ _) =
    case (ccw c a q, ccw c a r) of
      (CCW,CCW)      -> cmp
      (CCW,CW)       -> LT
      (CCW,CoLinear) | onZero r  -> GT
                     | otherwise -> LT
      (CW, CCW)      -> GT
      (CW, CW)       -> cmp
      (CW, CoLinear) -> GT
      (CoLinear, CCW) | onZero q  -> LT
                      | otherwise -> GT
      (CoLinear, CW)      -> LT
      (CoLinear,CoLinear) -> case (onZero q, onZero r) of
                               (True, True)   -> EQ
                               (False, False) -> EQ
                               (True, False)  -> LT
                               (False, True)  -> GT
  where
    a = c .+^ z
    b = c .+^ Vector2 (-zy) zx
    
    
    onZero d = case ccw c b d of
                 CCW      -> False
                 CW       -> True
                 CoLinear -> True 
    cmp = case ccw c q r of
            CCW      -> LT
            CW       -> GT
            CoLinear -> EQ
cwCmpAroundWith     :: (Ord r, Num r)
                    => Vector 2 r
                    -> Point 2 r :+ a
                    -> Point 2 r :+ b -> Point 2 r :+ c
                    -> Ordering
cwCmpAroundWith z c = flip (ccwCmpAroundWith z c)
cmpByDistanceTo              :: (Ord r, Num r, Arity d)
                             => Point d r :+ c -> Point d r :+ p -> Point d r :+ q -> Ordering
cmpByDistanceTo (c :+ _) p q = comparing (squaredEuclideanDist c) (p^.core) (q^.core)
ccwCmpAround :: (Num r, Ord r)
             => Point 2 r :+ qc -> Point 2 r :+ p -> Point 2 r :+ q -> Ordering
ccwCmpAround = ccwCmpAroundWith (Vector2 1 0)
cwCmpAround :: (Num r, Ord r)
            => Point 2 r :+ qc -> Point 2 r :+ p -> Point 2 r :+ q -> Ordering
cwCmpAround = cwCmpAroundWith (Vector2 1 0)
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 <> cmpByDistanceTo 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