| Copyright | (c) Ashley Moni, 2015 |
|---|---|
| License | BSD3 |
| Maintainer | Ashley Moni <ashley.moni1@gmail.com> |
| Stability | Stable |
| Safe Haskell | Safe |
| Language | Haskell2010 |
| Extensions |
|
Data.QuadTree
Contents
Description
The purpose of this module is to provide discrete region quadtrees that can be used as simple functional alternatives to 2D arrays, with lens support.
test = set (atLocation(0,0)) 'd' $ set (atLocation(5,5)) 'c' $ set (atLocation(3,2)) 'b' $ set (atLocation(2,4)) 'a' $makeTree(6,6) '.'
>>>printTree id testd..... ...... ...b.. ...... ..a... .....c
- data QuadTree a
- makeTree :: (Int, Int) -> a -> QuadTree a
- type Location = (Int, Int)
- atLocation :: forall a. Eq a => Location -> Lens' (QuadTree a) a
- getLocation :: Eq a => Location -> QuadTree a -> a
- setLocation :: Eq a => Location -> a -> QuadTree a -> QuadTree a
- mapLocation :: Eq a => Location -> (a -> a) -> QuadTree a -> QuadTree a
- fuseTree :: Eq a => QuadTree a -> QuadTree a
- tmap :: Eq b => (a -> b) -> QuadTree a -> QuadTree b
- filterTree :: (a -> Bool) -> QuadTree a -> [a]
- sortTreeBy :: (a -> a -> Ordering) -> QuadTree a -> [a]
- type Region = (Int, Int, Int, Int)
- type Tile a = (a, Region)
- tile :: QuadTree a -> [Tile a]
- expand :: [Tile a] -> [a]
- foldTiles :: forall a b. (Tile a -> b -> b) -> b -> QuadTree a -> b
- filterTiles :: (a -> Bool) -> [Tile a] -> [Tile a]
- sortTilesBy :: (a -> a -> Ordering) -> [Tile a] -> [Tile a]
- showTree :: Eq a => (a -> Char) -> QuadTree a -> String
- printTree :: Eq a => (a -> Char) -> QuadTree a -> IO ()
- outOfBounds :: Location -> QuadTree a -> Bool
- treeDimensions :: QuadTree a -> (Int, Int)
- regionArea :: Region -> Int
- inRegion :: Location -> Region -> Bool
Data Type & Constructor
The eponymous data type.
QuadTree is itself a wrapper around an internal tree structure
along with spatial metadata about the boundaries and depth of the
2D area it maps to.
Instances
| Functor QuadTree Source |
|
| Foldable QuadTree Source |
|
| Eq a => Eq (QuadTree a) Source | |
| Read a => Read (QuadTree a) Source | |
| Show a => Show (QuadTree a) Source |
Constructor that generates a QuadTree of the given dimensions,
with all cells filled with a default value.
Index access
This provides an array-style interface to the QuadTree, albeit
with an O(log n) lookup and insertion speed. This is both faster
and slower than an actual array (O(1) lookup and O(n) insertion
respectively).
The user can imagine a two dimensional grid that can be modified or queried via co-ordinate pair indices.
atLocation :: forall a. Eq a => Location -> Lens' (QuadTree a) a Source
Lens for accessing and manipulating data at a specific location.
getLocation :: Eq a => Location -> QuadTree a -> a Source
Getter for the value at a given location for a QuadTree.
Functor
fuseTree :: Eq a => QuadTree a -> QuadTree a Source
Cleanup function for use after any fmap.
When elements of a QuadTree are modified by setLocation (or
the atLocation lens), it automatically compresses identical
adjacent nodes into larger ones. This keeps the QuadTree from
bloating over constant use.
fmap does not do this. If you wish to treat the
QuadTree as a Functor, you should compose this
function after to collapse it down to its minimum size.
Example:
This particular example is reified in the function below.fuseTree $ fmap fn tree
Foldable
QuadTrees can be folded just like lists. If you simply replace
the Prelude fold functions with Data.Foldable ones...
import Data.Foldable import Prelude hiding (foldr, foldl, any, sum, find...)
... Then you can directly call them on QuadTrees without
qualification. No list functionality will be lost since the
Data.Foldable functions also work exactly like the Prelude
folds for list processing.
In addition you also get some extras like toList.
sortTreeBy :: (a -> a -> Ordering) -> QuadTree a -> [a] Source
Tiles
Directly folding a QuadTree will expand it into a sequence of
elements that are then folded over. For some types of operations
this can be incredibly inefficient; it may be faster to simply
manipulate a sequence of leaves and then later decompose the
results into a list of elements.
For these operations, we can use Tiles. Tiles are simply
blocks of elements, represented by a tuple of the leaf data and
some information on the spatial location and dimensions of the
block.
type Region = (Int, Int, Int, Int) Source
Rectangular area, represented by a tuple of four Ints.
They correspond to (X floor, Y floor, X ceiling, Y ceiling).
The co-ordinates are inclusive of all the rows and columns in all four Ints.
regionArea (x, y, x, y) == 1
Tile functions
The bread and butter method of manipulating Tiles is to first
decompose a QuadTree with tile, process the intermediate
representation, and then decompose it into a final list of elements
with expand.
expand. fn .tile$ tree
sortTilesBy :: (a -> a -> Ordering) -> [Tile a] -> [Tile a] Source
Printers
Arguments
| :: Eq a | |
| => (a -> Char) | Function to generate characters for each
|
| -> QuadTree a | |
| -> IO () |
As showTree above, but also prints it.
Miscellaneous helpers
outOfBounds :: Location -> QuadTree a -> Bool Source
Dimensions of a QuadTree, as an Int pair.
regionArea :: Region -> Int Source