| Copyright | Copyright (c) 2015 Birte Wagner Sebastian Philipp Copyright (c) 2022 Oleksii Divak  | 
|---|---|
| License | MIT | 
| Maintainer | Oleksii Divak | 
| Stability | experimental | 
| Portability | not portable | 
| Safe Haskell | Safe-Inferred | 
| Language | Haskell2010 | 
Data.R2Tree.Float.Unsafe
Contents
Description
Underlying implementation of the R2Tree.
Synopsis
- data MBR where
 - data R2Tree a
 - validMBR :: MBR -> Bool
 - eqMBR :: MBR -> MBR -> Bool
 - unionMBR :: MBR -> MBR -> MBR
 - areaMBR :: MBR -> Float
 - marginMBR :: MBR -> Float
 - distanceMBR :: MBR -> MBR -> Float
 - containsMBR :: MBR -> MBR -> Bool
 - containsMBR' :: MBR -> MBR -> Bool
 - intersectionMBR :: MBR -> MBR -> Maybe MBR
 - intersectionMBR' :: MBR -> MBR -> Maybe MBR
 - data Predicate = Predicate (MBR -> Bool) (MBR -> Bool)
 
Documentation
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} \).  | 
Bundled Patterns
| pattern MBR | Reorders coordinates to fit internal invariants. Pattern matching guarantees \( x_{0} \le x_{1}, y_{0} \le y_{1} \).  | 
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.
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
| Foldable R2Tree Source # | |
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 # elem :: Eq a => a -> R2Tree a -> Bool # maximum :: Ord a => R2Tree a -> a # minimum :: Ord a => R2Tree a -> a #  | |
| Eq1 R2Tree Source # | |
| Show1 R2Tree Source # | |
| Traversable R2Tree Source # | |
| Functor R2Tree Source # | Uses   | 
| NFData1 R2Tree Source # | |
Defined in Data.R2Tree.Float.Internal  | |
| Show a => Show (R2Tree a) Source # | |
| NFData a => NFData (R2Tree a) Source # | |
Defined in Data.R2Tree.Float.Internal  | |
| Eq a => Eq (R2Tree a) Source # | |
Common operations
validMBR :: MBR -> Bool Source #
Check whether lower endpoints are smaller or equal to the respective upper ones.
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 without touching any of the sides.
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.