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.Unsafe

Description

Underlying implementation of the R2Tree.

Synopsis

Documentation

data MBR 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.

Constructors

UnsafeMBR

Invariants: \( x_{min} \le x_{max}, y_{min} \le y_{max} \).

Fields

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 #

R-tree

Each MBR is tied to the value directly after it.

Invariant: the MBR of each non-leaf node encloses all the MBRs inside the node.

data R2Tree a Source #

Spine-strict two-dimensional R-tree.

Constructors

Node2 !MBR !(R2Tree a) !MBR !(R2Tree a) 
Node3 !MBR !(R2Tree a) !MBR !(R2Tree a) !MBR !(R2Tree a) 
Node4 !MBR !(R2Tree a) !MBR !(R2Tree a) !MBR !(R2Tree a) !MBR !(R2Tree a) 
Leaf2 !MBR a !MBR a 
Leaf3 !MBR a !MBR a !MBR a 
Leaf4 !MBR a !MBR a !MBR a !MBR a 
Leaf1 !MBR a

Invariant: only allowed as the root node.

Empty

Invariant: only allowed as the root node.

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 #

Common operations

validMBR :: MBR -> Bool Source #

Check whether lower endpoints are smaller or equal to the respective upper ones.

eqMBR :: MBR -> MBR -> Bool Source #

Check whether two rectangles are equal.

unionMBR :: MBR -> MBR -> MBR Source #

Resulting rectangle contains both input rectangles.

areaMBR :: MBR -> Float Source #

Proper area.

marginMBR :: MBR -> Float Source #

Half a perimeter.

distanceMBR :: MBR -> MBR -> Float Source #

Square distance between double the centers of two rectangles.

containsMBR :: MBR -> MBR -> Bool Source #

Whether left rectangle contains right one.

containsMBR' :: MBR -> MBR -> Bool Source #

Whether left rectangle contains right one without touching any of the sides.

intersectionMBR :: MBR -> MBR -> Maybe MBR Source #

Intersection of two rectangles, if any exists.

intersectionMBR' :: MBR -> MBR -> Maybe MBR Source #

Intersection of two rectangles, if any exists, excluding the side cases where the result would be a point or a line.

Range

data Predicate Source #

Comparison function.

Constructors

Predicate 

Fields