module Data.Geometry.Point.Quadrants where
import Control.DeepSeq
import Control.Lens
import Data.Aeson
import Data.Ext
import qualified Data.Foldable as F
import Data.Geometry.Point.Class
import Data.Geometry.Point.Internal
import Data.Geometry.Properties
import Data.Geometry.Vector
import qualified Data.Geometry.Vector as Vec
import Data.Hashable
import qualified Data.List as L
import Data.Ord (comparing)
import Data.Proxy
import GHC.Generics (Generic)
import GHC.TypeLits
import System.Random (Random(..))
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)
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