module Graphics.Gloss.Data.QuadTree
( QuadTree (..)
, emptyTree
, emptyNode
, takeQuadOfTree
, liftToQuad
, insertByPath
, insertByCoord
, lookupNodeByPath
, lookupByPath
, lookupByCoord
, flattenQuadTree
, flattenQuadTreeWithExtents)
where
import Graphics.Gloss.Data.Quad
import Graphics.Gloss.Data.Extent
data QuadTree a
= TNil
| TLeaf a
| TNode (QuadTree a) (QuadTree a)
(QuadTree a) (QuadTree a)
deriving Show
emptyTree :: QuadTree a
emptyTree = TNil
emptyNode :: QuadTree a
emptyNode = TNode TNil TNil TNil TNil
takeQuadOfTree
:: Quad
-> QuadTree a
-> Maybe (QuadTree a)
takeQuadOfTree quad tree
= case tree of
TNil -> Nothing
TLeaf{} -> Nothing
TNode nw ne sw se
-> case quad of
NW -> Just nw
NE -> Just ne
SW -> Just sw
SE -> Just se
liftToQuad
:: Quad
-> (QuadTree a -> QuadTree a)
-> QuadTree a -> QuadTree a
liftToQuad quad f tree
= case tree of
TNil -> tree
TLeaf{} -> tree
TNode nw ne sw se
-> case quad of
NW -> TNode (f nw) ne sw se
NE -> TNode nw (f ne) sw se
SW -> TNode nw ne (f sw) se
SE -> TNode nw ne sw (f se)
insertByPath :: [Quad] -> a -> QuadTree a -> QuadTree a
insertByPath [] x _
= TLeaf x
insertByPath (q:qs) x tree
= case tree of
TNil -> liftToQuad q (insertByPath qs x) emptyNode
TLeaf{} -> tree
TNode{} -> liftToQuad q (insertByPath qs x) tree
insertByCoord :: Extent -> Coord -> a -> QuadTree a -> Maybe (QuadTree a)
insertByCoord extent coord x tree
= do path <- pathToCoord extent coord
return $ insertByPath path x tree
lookupNodeByPath
:: [Quad]
-> QuadTree a
-> Maybe (QuadTree a)
lookupNodeByPath [] tree
= Just tree
lookupNodeByPath (q:qs) tree
= case tree of
TNil -> Nothing
TLeaf{} -> Nothing
TNode{}
-> let Just quad = takeQuadOfTree q tree
in lookupNodeByPath qs quad
lookupByPath :: [Quad] -> QuadTree a -> Maybe a
lookupByPath path tree
= case lookupNodeByPath path tree of
Just (TLeaf x) -> Just x
_ -> Nothing
lookupByCoord
:: forall a
. Extent
-> Coord
-> QuadTree a
-> Maybe a
lookupByCoord extent coord tree
= do path <- pathToCoord extent coord
lookupByPath path tree
flattenQuadTree
:: forall a
. Extent
-> QuadTree a
-> [(Coord, a)]
flattenQuadTree extentInit treeInit
= flatten' extentInit treeInit
where flatten' extent tree
= case tree of
TNil -> []
TLeaf x
-> let (_, s, _, w) = takeExtent extent
in [((w, s), x)]
TNode{} -> concat $ map (flattenQuad extent tree) allQuads
flattenQuad extent tree quad
= let extent' = cutQuadOfExtent quad extent
Just tree' = takeQuadOfTree quad tree
in flatten' extent' tree'
flattenQuadTreeWithExtents
:: forall a
. Extent
-> QuadTree a
-> [(Extent, a)]
flattenQuadTreeWithExtents extentInit treeInit
= flatten' extentInit treeInit
where flatten' extent tree
= case tree of
TNil -> []
TLeaf x
-> [(extent, x)]
TNode{} -> concat $ map (flattenQuad extent tree) allQuads
flattenQuad extent tree quad
= let extent' = cutQuadOfExtent quad extent
Just tree' = takeQuadOfTree quad tree
in flatten' extent' tree'