r-tree-1.0.0.0: R-/R*-trees.
CopyrightCopyright (c) 2015 Birte Wagner Sebastian Philipp
Copyright (c) 2022 Oleksii Divak
LicenseMIT
MaintainerOleksii Divak
Stabilityexperimental
Portabilitynot portable
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.R2Tree.Float

Description

This module (and every module below it) is a duplicate of Data.R2Tree.Double, defined for Floats instead of Doubles.

Synopsis

Documentation

data MBR where Source #

Two-dimensional minimum bounding rectangle is defined as two intervals, each along a separate axis, where every endpoint is either bounded and closed (i.e. \( [a, b] \)), or infinity (i.e. \((\pm \infty, b]\)).

Degenerate intervals (i.e. \([a,a]\)) are permitted.

Bundled Patterns

pattern MBR

Reorders coordinates to fit internal invariants.

Pattern matching guarantees \( x_{0} \le x_{1}, y_{0} \le y_{1} \).

Fields

Instances

Instances details
Show MBR Source # 
Instance details

Defined in Data.R2Tree.Float.Internal

Methods

showsPrec :: Int -> MBR -> ShowS #

show :: MBR -> String #

showList :: [MBR] -> ShowS #

Eq MBR Source # 
Instance details

Defined in Data.R2Tree.Float.Internal

Methods

(==) :: MBR -> MBR -> Bool #

(/=) :: MBR -> MBR -> Bool #

data R2Tree a Source #

Spine-strict two-dimensional R-tree.

Instances

Instances details
Foldable R2Tree Source # 
Instance details

Defined in Data.R2Tree.Float.Internal

Methods

fold :: Monoid m => R2Tree m -> m #

foldMap :: Monoid m => (a -> m) -> R2Tree a -> m #

foldMap' :: Monoid m => (a -> m) -> R2Tree a -> m #

foldr :: (a -> b -> b) -> b -> R2Tree a -> b #

foldr' :: (a -> b -> b) -> b -> R2Tree a -> b #

foldl :: (b -> a -> b) -> b -> R2Tree a -> b #

foldl' :: (b -> a -> b) -> b -> R2Tree a -> b #

foldr1 :: (a -> a -> a) -> R2Tree a -> a #

foldl1 :: (a -> a -> a) -> R2Tree a -> a #

toList :: R2Tree a -> [a] #

null :: R2Tree a -> Bool #

length :: R2Tree a -> Int #

elem :: Eq a => a -> R2Tree a -> Bool #

maximum :: Ord a => R2Tree a -> a #

minimum :: Ord a => R2Tree a -> a #

sum :: Num a => R2Tree a -> a #

product :: Num a => R2Tree a -> a #

Eq1 R2Tree Source # 
Instance details

Defined in Data.R2Tree.Float.Internal

Methods

liftEq :: (a -> b -> Bool) -> R2Tree a -> R2Tree b -> Bool #

Show1 R2Tree Source # 
Instance details

Defined in Data.R2Tree.Float.Internal

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> R2Tree a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [R2Tree a] -> ShowS #

Traversable R2Tree Source # 
Instance details

Defined in Data.R2Tree.Float.Internal

Methods

traverse :: Applicative f => (a -> f b) -> R2Tree a -> f (R2Tree b) #

sequenceA :: Applicative f => R2Tree (f a) -> f (R2Tree a) #

mapM :: Monad m => (a -> m b) -> R2Tree a -> m (R2Tree b) #

sequence :: Monad m => R2Tree (m a) -> m (R2Tree a) #

Functor R2Tree Source #

Uses map.

Instance details

Defined in Data.R2Tree.Float.Internal

Methods

fmap :: (a -> b) -> R2Tree a -> R2Tree b #

(<$) :: a -> R2Tree b -> R2Tree a #

NFData1 R2Tree Source # 
Instance details

Defined in Data.R2Tree.Float.Internal

Methods

liftRnf :: (a -> ()) -> R2Tree a -> () #

Show a => Show (R2Tree a) Source # 
Instance details

Defined in Data.R2Tree.Float.Internal

Methods

showsPrec :: Int -> R2Tree a -> ShowS #

show :: R2Tree a -> String #

showList :: [R2Tree a] -> ShowS #

NFData a => NFData (R2Tree a) Source # 
Instance details

Defined in Data.R2Tree.Float.Internal

Methods

rnf :: R2Tree a -> () #

Eq a => Eq (R2Tree a) Source # 
Instance details

Defined in Data.R2Tree.Float.Internal

Methods

(==) :: R2Tree a -> R2Tree a -> Bool #

(/=) :: R2Tree a -> R2Tree a -> Bool #

Construct

empty :: R2Tree a Source #

\(\mathcal{O}(1)\). Empty tree.

singleton :: MBR -> a -> R2Tree a Source #

\(\mathcal{O}(1)\). Tree with a single entry.

doubleton :: MBR -> a -> MBR -> a -> R2Tree a Source #

\(\mathcal{O}(1)\). Tree with two entries.

tripleton :: MBR -> a -> MBR -> a -> MBR -> a -> R2Tree a Source #

\(\mathcal{O}(1)\). Tree with three entries.

quadrupleton :: MBR -> a -> MBR -> a -> MBR -> a -> MBR -> a -> R2Tree a Source #

\(\mathcal{O}(1)\). Tree with four entries.

Bulk-loading

bulkSTR :: [(MBR, a)] -> R2Tree a Source #

\(\mathcal{O}(n \log n)\). Bulk-load a tree.

bulkSTR uses the Sort-Tile-Recursive algorithm.

Single-key

Insert

insert :: MBR -> a -> R2Tree a -> R2Tree a Source #

\(\mathcal{O}(\log n)\). Insert a value into the tree.

insert uses the R*-tree insertion algorithm.

insertGut :: MBR -> a -> R2Tree a -> R2Tree a Source #

\(\mathcal{O}(\log n)\). Insert a value into the tree.

insertGut uses the R-tree insertion algorithm with quadratic-cost splits. Compared to insert the resulting trees are of lower quality (see the Wikipedia article for a graphic example).

Delete

delete :: MBR -> R2Tree a -> R2Tree a Source #

\(\mathcal{O}(\log n)\). Remove an entry stored under a given MBR, if one exists. If multiple entries qualify, the leftmost one is removed.

delete uses the R-tree deletion algorithm with quadratic-cost splits.

Range

data Predicate Source #

Comparison function.

equals :: MBR -> Predicate Source #

Matches exactly the provided MBR.

intersects :: MBR -> Predicate Source #

Matches any MBR that intersects the provided one.

intersects' :: MBR -> Predicate Source #

Matches any MBR that intersects the provided one, if the intersection is not a line or a point.

contains :: MBR -> Predicate Source #

Matches any MBR that contains the provided one.

contains' :: MBR -> Predicate Source #

Matches any MBR that contains the provided one, excluding ones that touch it on one or more sides.

containedBy :: MBR -> Predicate Source #

Matches any MBR that is contained within the provided one.

containedBy' :: MBR -> Predicate Source #

Matches any MBR that is contained within the provided one, excluding ones that touch it on one or more sides.

Map

adjustRangeWithKey :: Predicate -> (MBR -> a -> a) -> R2Tree a -> R2Tree a Source #

\(\mathcal{O}(\log n + n_I)\). Map a function over MBRs that match the Predicate and their respective values.

adjustRangeWithKey' :: Predicate -> (MBR -> a -> a) -> R2Tree a -> R2Tree a Source #

\(\mathcal{O}(\log n + n_I)\). Map a function over MBRs that match the Predicate and their respective values and evaluate the results to WHNF.

Fold

foldlRangeWithKey :: Predicate -> (b -> MBR -> a -> b) -> b -> R2Tree a -> b Source #

\(\mathcal{O}(\log n + n_{I_R})\). Fold left-to-right over MBRs that match the Predicate and their respective values.

foldrRangeWithKey :: Predicate -> (MBR -> a -> b -> b) -> b -> R2Tree a -> b Source #

\(\mathcal{O}(\log n + n_{I_L})\). Fold right-to-left over MBRs that match the Predicate and their respective values.

foldMapRangeWithKey :: Monoid m => Predicate -> (MBR -> a -> m) -> R2Tree a -> m Source #

\(\mathcal{O}(\log n + n_{I_M})\). Map each MBR that matches the Predicate and its respective value to a monoid and combine the results.

foldlRangeWithKey' :: Predicate -> (b -> MBR -> a -> b) -> b -> R2Tree a -> b Source #

\(\mathcal{O}(\log n + n_I)\). Fold left-to-right over MBRs that match the Predicate and their respective values, applying the operator function strictly.

foldrRangeWithKey' :: Predicate -> (MBR -> a -> b -> b) -> b -> R2Tree a -> b Source #

\(\mathcal{O}(\log n + n_I)\). Fold right-to-left over MBRs that match the Predicate and their respective values, applying the operator function strictly.

Traverse

traverseRangeWithKey :: Applicative f => Predicate -> (MBR -> a -> f a) -> R2Tree a -> f (R2Tree a) Source #

\(\mathcal{O}(\log n + n_I)\). Map each MBR that matches the Predicate and its respective value to an action, evaluate the actions left-to-right and collect the results.

Full tree

Size

null :: R2Tree a -> Bool Source #

\(\mathcal{O}(1)\). Check if the tree is empty.

size :: R2Tree a -> Int Source #

\(\mathcal{O}(n)\). Calculate the number of elements stored in the tree. The returned number is guaranteed to be non-negative.

Map

map :: (a -> b) -> R2Tree a -> R2Tree b Source #

\(\mathcal{O}(n)\). Map a function over all values.

map' :: (a -> b) -> R2Tree a -> R2Tree b Source #

\(\mathcal{O}(n)\). Map a function over all values and evaluate the results to WHNF.

mapWithKey :: (MBR -> a -> b) -> R2Tree a -> R2Tree b Source #

\(\mathcal{O}(n)\). Map a function over all MBRs and their respective values.

mapWithKey' :: (MBR -> a -> b) -> R2Tree a -> R2Tree b Source #

\(\mathcal{O}(n)\). Map a function over all MBRs and their respective values and evaluate the results to WHNF.

Fold

Left-to-right

foldl :: (b -> a -> b) -> b -> R2Tree a -> b Source #

\(\mathcal{O}(n_R)\). Fold left-to-right over all values.

foldl' :: (b -> a -> b) -> b -> R2Tree a -> b Source #

\(\mathcal{O}(n)\). Fold left-to-right over all values, applying the operator function strictly.

foldlWithKey :: (b -> MBR -> a -> b) -> b -> R2Tree a -> b Source #

\(\mathcal{O}(n_R)\). Fold left-to-right over all MBRs and their respective values.

foldlWithKey' :: (b -> MBR -> a -> b) -> b -> R2Tree a -> b Source #

\(\mathcal{O}(n)\). Fold left-to-right over all MBRs and their respective values, applying the operator function strictly.

Right-to-left

foldr :: (a -> b -> b) -> b -> R2Tree a -> b Source #

\(\mathcal{O}(n_L)\). Fold right-to-left over all values.

foldr' :: (a -> b -> b) -> b -> R2Tree a -> b Source #

\(\mathcal{O}(n)\). Fold right-to-left over all values, applying the operator function strictly.

foldrWithKey :: (MBR -> a -> b -> b) -> b -> R2Tree a -> b Source #

\(\mathcal{O}(n_L)\). Fold right-to-left over all MBRs and their respective values.

foldrWithKey' :: (MBR -> a -> b -> b) -> b -> R2Tree a -> b Source #

\(\mathcal{O}(n)\). Fold right-to-left over all MBRs and their respective values, applying the operator function strictly.

Monoid

foldMap :: Monoid m => (a -> m) -> R2Tree a -> m Source #

\(\mathcal{O}(n_M)\). Map each value to a monoid and combine the results.

foldMapWithKey :: Monoid m => (MBR -> a -> m) -> R2Tree a -> m Source #

\(\mathcal{O}(n_M)\). Map each MBR and its respective value to a monoid and combine the results.

Traverse

traverse :: Applicative f => (a -> f b) -> R2Tree a -> f (R2Tree b) Source #

\(\mathcal{O}(n)\). Map each value to an action, evaluate the actions left-to-right and collect the results.

traverseWithKey :: Applicative f => (MBR -> a -> f b) -> R2Tree a -> f (R2Tree b) Source #

\(\mathcal{O}(n)\). Map each MBR and its respective value to an action, evaluate the actions left-to-right and collect the results.