module Data.Geometry.PrioritySearchTree( PrioritySearchTree(..)
                                       , createTree
                                       , queryRange
                                       ) where
import           Algorithms.DivideAndConquer (mergeSortedListsBy)
import           Control.Lens
import           Data.BinaryTree
import           Data.Ext
import           Data.Geometry.Point
import           Data.List.NonEmpty (NonEmpty(..))
import qualified Data.List.NonEmpty as NonEmpty
import           Data.Measured.Class ()
import           Data.Measured.Size
import           Data.Ord (comparing, Down(..))
import           Data.Range
import qualified Data.Set as Set
import           Data.Util
data NodeData p r = NodeData { _splitPoint :: !r
                             , _maxVal     :: !(Maybe (Point 2 r :+ p))
                             } deriving (Show,Eq)
instance Bifunctor NodeData where
  bimap f g (NodeData x m) = NodeData (g x) ((bimap (fmap g) f) <$> m)
maxVal :: Lens' (NodeData p r) (Maybe (Point 2 r :+ p))
maxVal = lens _maxVal (\(NodeData x _) m -> NodeData x m)
type LeafData p r = SP r [Point 2 r :+ p]
newtype PrioritySearchTree p r =
    PrioritySearchTree { _unPrioritySearchTree :: BinLeafTree (NodeData p r) (LeafData p r) }
  deriving (Show,Eq)
instance Bifunctor PrioritySearchTree where
  
  
  
  bimap f g (PrioritySearchTree t) = PrioritySearchTree . bimap (bimap f g) h $ t
    where
      h = bimap g (map $ bimap (fmap g) f)
createTree     :: Ord r => NonEmpty (Point 2 r :+ p) -> PrioritySearchTree p r
createTree pts = PrioritySearchTree $ foldr insert t pts
  where
    t = view _1
      . foldUp (\(SP l k) _ (SP r m) -> SP (Node l (NodeData k Nothing) r) m)
               (\(Elem x) -> SP (Leaf (SP x [])) x)
      . asBalancedBinLeafTree . NonEmpty.fromList
      . Set.toAscList . Set.fromList 
      . map (^.core.xCoord) . NonEmpty.toList $ pts
insert                          :: Ord r
                                => Point 2 r :+ p
                                -> BinLeafTree (NodeData p r) (LeafData p r)
                                -> BinLeafTree (NodeData p r) (LeafData p r)
insert p = \case
    Leaf (SP x ps)                                -> Leaf $ SP x (p:ps)
      
      
    Node l d r | py > d^?maxVal._Just.core.yCoord ->
                   node' l (d&maxVal .~ Just p) r (d^.maxVal)
                   
               | otherwise                 ->
                   node' l d                             r (Just p)
  where
    py = Just $ p^.core.yCoord
    node' l d@(NodeData k _) r = \case
      Nothing                      -> Node l d r 
      Just q | q^.core.xCoord <= k -> Node (insert q l) d r
             | otherwise           -> Node l d (insert q r)
queryRange   :: Ord r
             => (Range r,r) -> PrioritySearchTree p r -> [Point 2 r :+ p]
queryRange q = queryRange' q . _unPrioritySearchTree
queryRange'           :: Ord r
                      => (Range r,r) -> BinLeafTree (NodeData p r) (LeafData p r)
                      -> [Point 2 r :+ p]
queryRange' q@(qr, y) = \case
    Leaf (SP x pts) | x `inRange` qr                     ->
                        takeWhile (\p -> p^.core.yCoord >= y) pts
                    | otherwise                          -> []
    Node _ (NodeData _ Nothing)  _                       -> []
      
    Node l (NodeData x (Just p)) r | p^.core.yCoord >= y -> mrep p <> merge (goL x l) (goR x r)
                                   | otherwise           -> []
                                     
                                     
  where
    mrep p | (p^.core.xCoord) `inRange` qr = [p]
           | otherwise                     = []
    goL x t' | qr^.lower <= Closed x = queryRange' q t'
             | otherwise             = []
    goR x t' | Open x < qr^.upper    = queryRange' q t'
             | otherwise             = []
    merge = mergeSortedListsBy $ comparing (Down . (^.core.yCoord))