module Graphics.Gloss.Algorithms.RayCast
( castSegIntoCellularQuadTree
, traceSegIntoCellularQuadTree)
where
import Graphics.Gloss.Data.Picture
import Graphics.Gloss.Data.Quad
import Graphics.Gloss.Data.Extent
import Graphics.Gloss.Data.QuadTree
import Data.List
import Data.Function
castSegIntoCellularQuadTree
:: forall a
. Point
-> Point
-> Extent
-> QuadTree a
-> Maybe (Point, Extent, a)
castSegIntoCellularQuadTree p1 p2 extent tree
| cells@(_:_) <- traceSegIntoCellularQuadTree p1 p2 extent tree
, c : _ <- sortBy ((compareDistanceTo p1) `on` (\(a, _, _) -> a) ) cells
= Just c
| otherwise
= Nothing
compareDistanceTo :: Point -> Point -> Point -> Ordering
compareDistanceTo p0 p1 p2
= let d1 = distance p0 p1
d2 = distance p0 p2
in compare d1 d2
distance :: Point -> Point -> Float
distance (x1, y1) (x2, y2)
= let xd = x2 x1
yd = y2 y1
in sqrt (xd * xd + yd * yd)
traceSegIntoCellularQuadTree
:: forall a
. Point
-> Point
-> Extent
-> QuadTree a
-> [(Point, Extent, a)]
traceSegIntoCellularQuadTree p1 p2 extent tree
= case tree of
TNil -> []
TLeaf a
-> case intersectSegExtent p1 p2 extent of
Just pos -> [(pos, extent, a)]
Nothing -> []
TNode nw ne sw se
| touchesSegExtent p1 p2 extent
-> concat
[ traceSegIntoCellularQuadTree p1 p2 (cutQuadOfExtent NW extent) nw
, traceSegIntoCellularQuadTree p1 p2 (cutQuadOfExtent NE extent) ne
, traceSegIntoCellularQuadTree p1 p2 (cutQuadOfExtent SW extent) sw
, traceSegIntoCellularQuadTree p1 p2 (cutQuadOfExtent SE extent) se ]
_ -> []