{-# LANGUAGE BangPatterns
           , PatternSynonyms
           , RankNTypes
           , ViewPatterns
           , UnboxedTuples #-}

module Data.R2Tree.Double.Internal
  ( MBR (UnsafeMBR, MBR)
  , validMBR
  , eqMBR
  , unionMBR
  , areaMBR
  , marginMBR
  , distanceMBR
  , containsMBR
  , containsMBR'
  , intersectionMBR
  , intersectionMBR'

  , Predicate (..)
  , equals
  , intersects
  , intersects'
  , contains
  , contains'
  , containedBy
  , containedBy'

  , R2Tree (..)

  , Data.R2Tree.Double.Internal.null
  , Data.R2Tree.Double.Internal.size

  , Data.R2Tree.Double.Internal.map
  , map'
  , mapWithKey
  , mapWithKey'
  , adjustRangeWithKey
  , adjustRangeWithKey'

  , Data.R2Tree.Double.Internal.foldl
  , Data.R2Tree.Double.Internal.foldl'
  , foldlWithKey
  , foldlWithKey'
  , foldlRangeWithKey
  , foldlRangeWithKey'

  , Data.R2Tree.Double.Internal.foldr
  , Data.R2Tree.Double.Internal.foldr'
  , foldrWithKey
  , foldrWithKey'
  , foldrRangeWithKey
  , foldrRangeWithKey'

  , Data.R2Tree.Double.Internal.foldMap
  , foldMapWithKey
  , foldMapRangeWithKey

  , Data.R2Tree.Double.Internal.traverse
  , traverseWithKey
  , traverseRangeWithKey

  , insertGut
  , insert
  , delete

  , bulkSTR
  ) where

import           Control.Applicative
import           Control.DeepSeq
import           Data.Bits
import           Data.Foldable
import           Data.Functor.Classes
import           Data.Function
import qualified Data.List as List
import           Data.List.NonEmpty (NonEmpty (..), (<|))
import           Text.Show



-- | 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.
data MBR = -- | Invariants: \( x_{min} \le x_{max}, y_{min} \le y_{max} \).
           UnsafeMBR
             {-# UNPACK #-} !Double -- ^ \( x_{min} \)
             {-# UNPACK #-} !Double -- ^ \( y_{min} \)
             {-# UNPACK #-} !Double -- ^ \( x_{max} \)
             {-# UNPACK #-} !Double -- ^ \( y_{max} \)

{-# COMPLETE MBR #-}
-- | Reorders coordinates to fit internal invariants.
--
--   Pattern matching guarantees \( x_{0} \le x_{1}, y_{0} \le y_{1} \).
pattern MBR
  :: Double -- ^ \( x_0 \)
  -> Double -- ^ \( y_0 \)
  -> Double -- ^ \( x_1 \)
  -> Double -- ^ \( y_1 \)
  -> MBR
pattern $mMBR :: forall {r}.
MBR
-> (Double -> Double -> Double -> Double -> r) -> ((# #) -> r) -> r
$bMBR :: Double -> Double -> Double -> Double -> MBR
MBR xmin ymin xmax ymax <- UnsafeMBR xmin ymin xmax ymax
  where
    MBR Double
x0 Double
y0 Double
x1 Double
y1 =
      let !(# Double
xmin, Double
xmax #) | Double
x0 Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
<= Double
x1  = (# Double
x0, Double
x1 #)
                            | Bool
otherwise = (# Double
x1, Double
x0 #)

          !(# Double
ymin, Double
ymax #) | Double
y0 Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
<= Double
y1  = (# Double
y0, Double
y1 #)
                            | Bool
otherwise = (# Double
y1, Double
y0 #)

      in Double -> Double -> Double -> Double -> MBR
UnsafeMBR Double
xmin Double
ymin Double
xmax Double
ymax

instance Show MBR where
  showsPrec :: Int -> MBR -> ShowS
showsPrec Int
d (UnsafeMBR Double
xmin Double
ymin Double
xmax Double
ymax) =
    Bool -> ShowS -> ShowS
showParen (Int
d Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
10) (ShowS -> ShowS) -> ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$ String -> ShowS
showString String
"MBR " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Double -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
11 Double
xmin
                            ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar Char
' ' ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Double -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
11 Double
ymin
                            ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar Char
' ' ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Double -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
11 Double
xmax
                            ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar Char
' ' ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Double -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
11 Double
ymax

instance Eq MBR where
  == :: MBR -> MBR -> Bool
(==) = MBR -> MBR -> Bool
eqMBR



-- | Check whether lower endpoints are smaller or equal to the respective upper ones.
validMBR :: MBR -> Bool
validMBR :: MBR -> Bool
validMBR (MBR Double
xmin Double
ymin Double
xmax Double
ymax) = Double
xmin Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
<= Double
xmax Bool -> Bool -> Bool
&& Double
ymin Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
<= Double
ymax

{-# INLINE eqMBR #-}
-- | Check whether two rectangles are equal.
eqMBR :: MBR -> MBR -> Bool
eqMBR :: MBR -> MBR -> Bool
eqMBR (MBR Double
xmin Double
ymin Double
xmax Double
ymax) (MBR Double
xmin' Double
ymin' Double
xmax' Double
ymax') =
  Double
xmin Double -> Double -> Bool
forall a. Eq a => a -> a -> Bool
== Double
xmin' Bool -> Bool -> Bool
&& Double
ymin Double -> Double -> Bool
forall a. Eq a => a -> a -> Bool
== Double
ymin' Bool -> Bool -> Bool
&& Double
xmax Double -> Double -> Bool
forall a. Eq a => a -> a -> Bool
== Double
xmax' Bool -> Bool -> Bool
&& Double
ymax Double -> Double -> Bool
forall a. Eq a => a -> a -> Bool
== Double
ymax'


{-# INLINE unionMBR #-}
-- | Resulting rectangle contains both input rectangles.
unionMBR :: MBR -> MBR -> MBR
unionMBR :: MBR -> MBR -> MBR
unionMBR (MBR Double
xmin Double
ymin Double
xmax Double
ymax) (MBR Double
xmin' Double
ymin' Double
xmax' Double
ymax') =
  Double -> Double -> Double -> Double -> MBR
MBR (Double -> Double -> Double
forall a. Ord a => a -> a -> a
min Double
xmin Double
xmin') (Double -> Double -> Double
forall a. Ord a => a -> a -> a
min Double
ymin Double
ymin') (Double -> Double -> Double
forall a. Ord a => a -> a -> a
max Double
xmax Double
xmax') (Double -> Double -> Double
forall a. Ord a => a -> a -> a
max Double
ymax Double
ymax')


{-# INLINE areaMBR #-}
-- | Proper area.
areaMBR :: MBR -> Double
areaMBR :: MBR -> Double
areaMBR (MBR Double
xmin Double
ymin Double
xmax Double
ymax) = (Double
xmax Double -> Double -> Double
forall a. Num a => a -> a -> a
- Double
xmin) Double -> Double -> Double
forall a. Num a => a -> a -> a
* (Double
ymax Double -> Double -> Double
forall a. Num a => a -> a -> a
- Double
ymin)

{-# INLINE marginMBR #-}
-- | Half a perimeter.
marginMBR :: MBR -> Double
marginMBR :: MBR -> Double
marginMBR (MBR Double
xmin Double
ymin Double
xmax Double
ymax) = (Double
xmax Double -> Double -> Double
forall a. Num a => a -> a -> a
- Double
xmin) Double -> Double -> Double
forall a. Num a => a -> a -> a
+ (Double
ymax Double -> Double -> Double
forall a. Num a => a -> a -> a
- Double
ymin)

{-# INLINE overlapMBR #-}
overlapMBR :: MBR -> MBR -> Double
overlapMBR :: MBR -> MBR -> Double
overlapMBR =
  (Double -> Double -> Double -> Double -> Double)
-> MBR -> MBR -> Double
forall a.
(Double -> Double -> Double -> Double -> a) -> MBR -> MBR -> a
intersectionMBR_ ((Double -> Double -> Double -> Double -> Double)
 -> MBR -> MBR -> Double)
-> (Double -> Double -> Double -> Double -> Double)
-> MBR
-> MBR
-> Double
forall a b. (a -> b) -> a -> b
$ \Double
x Double
y Double
x' Double
y' ->
    if Double
x Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
< Double
x' Bool -> Bool -> Bool
&& Double
y Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
< Double
y'
      then MBR -> Double
areaMBR (Double -> Double -> Double -> Double -> MBR
MBR Double
x Double
y Double
x' Double
y')
      else Double
0


{-# INLINE distanceMBR #-}
-- | Square distance between double the centers of two rectangles.
distanceMBR :: MBR -> MBR -> Double
distanceMBR :: MBR -> MBR -> Double
distanceMBR (MBR Double
xmin Double
ymin Double
xmax Double
ymax) (MBR Double
xmin' Double
ymin' Double
xmax' Double
ymax') =
  let x :: Double
x = (Double
xmax' Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double
xmin') Double -> Double -> Double
forall a. Num a => a -> a -> a
- (Double
xmax Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double
xmin)
      y :: Double
y = (Double
ymax' Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double
ymin') Double -> Double -> Double
forall a. Num a => a -> a -> a
- (Double
ymax Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double
ymin)
  in Double
x Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
x Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double
y Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
y


{-# INLINE containsMBR #-}
-- | Whether left rectangle contains right one.
containsMBR :: MBR -> MBR -> Bool
containsMBR :: MBR -> MBR -> Bool
containsMBR (MBR Double
xmin Double
ymin Double
xmax Double
ymax) (MBR Double
xmin' Double
ymin' Double
xmax' Double
ymax') =
  Double
xmin Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
<= Double
xmin' Bool -> Bool -> Bool
&& Double
ymin Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
<= Double
ymin' Bool -> Bool -> Bool
&& Double
xmax Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
>= Double
xmax' Bool -> Bool -> Bool
&& Double
ymax Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
>= Double
ymax'

{-# INLINE containsMBR' #-}
-- | Whether left rectangle contains right one without touching any of the sides.
containsMBR' :: MBR -> MBR -> Bool
containsMBR' :: MBR -> MBR -> Bool
containsMBR' (MBR Double
xmin Double
ymin Double
xmax Double
ymax) (MBR Double
xmin' Double
ymin' Double
xmax' Double
ymax') =
  Double
xmin Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
< Double
xmin' Bool -> Bool -> Bool
&& Double
ymin Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
< Double
ymin' Bool -> Bool -> Bool
&& Double
xmax Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
> Double
xmax' Bool -> Bool -> Bool
&& Double
ymax Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
> Double
ymax'



{-# INLINE intersectionMBR #-}
-- | Intersection of two rectangles, if any exists.
intersectionMBR :: MBR -> MBR -> Maybe MBR
intersectionMBR :: MBR -> MBR -> Maybe MBR
intersectionMBR =
  (Double -> Double -> Double -> Double -> Maybe MBR)
-> MBR -> MBR -> Maybe MBR
forall a.
(Double -> Double -> Double -> Double -> a) -> MBR -> MBR -> a
intersectionMBR_ ((Double -> Double -> Double -> Double -> Maybe MBR)
 -> MBR -> MBR -> Maybe MBR)
-> (Double -> Double -> Double -> Double -> Maybe MBR)
-> MBR
-> MBR
-> Maybe MBR
forall a b. (a -> b) -> a -> b
$ \Double
x Double
y Double
x' Double
y' ->
    if Double
x Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
<= Double
x' Bool -> Bool -> Bool
&& Double
y Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
<= Double
y'
      then MBR -> Maybe MBR
forall a. a -> Maybe a
Just (Double -> Double -> Double -> Double -> MBR
MBR Double
x Double
y Double
x' Double
y')
      else Maybe MBR
forall a. Maybe a
Nothing

{-# INLINE intersectionMBR' #-}
-- | Intersection of two rectangles, if any exists, excluding the side cases where
--   the result would be a point or a line.
intersectionMBR' :: MBR -> MBR -> Maybe MBR
intersectionMBR' :: MBR -> MBR -> Maybe MBR
intersectionMBR' =
  (Double -> Double -> Double -> Double -> Maybe MBR)
-> MBR -> MBR -> Maybe MBR
forall a.
(Double -> Double -> Double -> Double -> a) -> MBR -> MBR -> a
intersectionMBR_ ((Double -> Double -> Double -> Double -> Maybe MBR)
 -> MBR -> MBR -> Maybe MBR)
-> (Double -> Double -> Double -> Double -> Maybe MBR)
-> MBR
-> MBR
-> Maybe MBR
forall a b. (a -> b) -> a -> b
$ \Double
x Double
y Double
x' Double
y' ->
    if Double
x Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
< Double
x' Bool -> Bool -> Bool
&& Double
y Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
< Double
y'
      then MBR -> Maybe MBR
forall a. a -> Maybe a
Just (Double -> Double -> Double -> Double -> MBR
MBR Double
x Double
y Double
x' Double
y')
      else Maybe MBR
forall a. Maybe a
Nothing

{-# INLINE intersectionMBR_ #-}
intersectionMBR_ :: (Double -> Double -> Double -> Double -> a) -> MBR -> MBR -> a
intersectionMBR_ :: forall a.
(Double -> Double -> Double -> Double -> a) -> MBR -> MBR -> a
intersectionMBR_ Double -> Double -> Double -> Double -> a
f (MBR Double
xmin Double
ymin Double
xmax Double
ymax) (MBR Double
xmin' Double
ymin' Double
xmax' Double
ymax') =
  let x :: Double
x  = Double -> Double -> Double
forall a. Ord a => a -> a -> a
max Double
xmin Double
xmin'
      y :: Double
y  = Double -> Double -> Double
forall a. Ord a => a -> a -> a
max Double
ymin Double
ymin'
      x' :: Double
x' = Double -> Double -> Double
forall a. Ord a => a -> a -> a
min Double
xmax Double
xmax'
      y' :: Double
y' = Double -> Double -> Double
forall a. Ord a => a -> a -> a
min Double
ymax Double
ymax'

  in Double -> Double -> Double -> Double -> a
f Double
x Double
y Double
x' Double
y'

{-# INLINE intersectsMBR #-}
intersectsMBR :: MBR -> MBR -> Bool
intersectsMBR :: MBR -> MBR -> Bool
intersectsMBR = (Double -> Double -> Double -> Double -> Bool)
-> MBR -> MBR -> Bool
forall a.
(Double -> Double -> Double -> Double -> a) -> MBR -> MBR -> a
intersectionMBR_ ((Double -> Double -> Double -> Double -> Bool)
 -> MBR -> MBR -> Bool)
-> (Double -> Double -> Double -> Double -> Bool)
-> MBR
-> MBR
-> Bool
forall a b. (a -> b) -> a -> b
$ \Double
x Double
y Double
x' Double
y' -> Double
x Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
<= Double
x' Bool -> Bool -> Bool
&& Double
y Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
<= Double
y'

{-# INLINE intersectsMBR' #-}
intersectsMBR' :: MBR -> MBR -> Bool
intersectsMBR' :: MBR -> MBR -> Bool
intersectsMBR' = (Double -> Double -> Double -> Double -> Bool)
-> MBR -> MBR -> Bool
forall a.
(Double -> Double -> Double -> Double -> a) -> MBR -> MBR -> a
intersectionMBR_ ((Double -> Double -> Double -> Double -> Bool)
 -> MBR -> MBR -> Bool)
-> (Double -> Double -> Double -> Double -> Bool)
-> MBR
-> MBR
-> Bool
forall a b. (a -> b) -> a -> b
$ \Double
x Double
y Double
x' Double
y' -> Double
x Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
< Double
x' Bool -> Bool -> Bool
&& Double
y Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
< Double
y'



-- | Comparison function.
data Predicate = Predicate
                   (MBR -> Bool) -- ^ Matches nodes
                   (MBR -> Bool) -- ^ Matches leaves

{-# INLINE equals #-}
-- | Matches exactly the provided t'MBR'.
equals :: MBR -> Predicate
equals :: MBR -> Predicate
equals MBR
bx = (MBR -> Bool) -> (MBR -> Bool) -> Predicate
Predicate (\MBR
ba -> MBR -> MBR -> Bool
containsMBR MBR
ba MBR
bx) (MBR -> MBR -> Bool
eqMBR MBR
bx)

{-# INLINE intersects #-}
-- | Matches any t'MBR' that intersects the provided one.
intersects:: MBR -> Predicate
intersects :: MBR -> Predicate
intersects MBR
bx = (MBR -> Bool) -> (MBR -> Bool) -> Predicate
Predicate (MBR -> MBR -> Bool
intersectsMBR MBR
bx) (MBR -> MBR -> Bool
intersectsMBR MBR
bx)

{-# INLINE intersects' #-}
-- | Matches any t'MBR' that intersects the provided one, if the
--   intersection is not a line or a point.
intersects' :: MBR -> Predicate
intersects' :: MBR -> Predicate
intersects' MBR
bx = (MBR -> Bool) -> (MBR -> Bool) -> Predicate
Predicate (MBR -> MBR -> Bool
intersectsMBR' MBR
bx) (MBR -> MBR -> Bool
intersectsMBR' MBR
bx)

{-# INLINE contains #-}
-- | Matches any t'MBR' that contains the provided one.
contains :: MBR -> Predicate
contains :: MBR -> Predicate
contains MBR
bx = (MBR -> Bool) -> (MBR -> Bool) -> Predicate
Predicate (\MBR
ba -> MBR -> MBR -> Bool
containsMBR MBR
ba MBR
bx) (\MBR
ba -> MBR -> MBR -> Bool
containsMBR MBR
ba MBR
bx)

{-# INLINE contains' #-}
-- | Matches any t'MBR' that contains the provided one,
--   excluding ones that touch it on one or more sides.
contains' :: MBR -> Predicate
contains' :: MBR -> Predicate
contains' MBR
bx = (MBR -> Bool) -> (MBR -> Bool) -> Predicate
Predicate (\MBR
ba -> MBR -> MBR -> Bool
containsMBR MBR
ba MBR
bx) (\MBR
ba -> MBR -> MBR -> Bool
containsMBR' MBR
ba MBR
bx)

{-# INLINE containedBy #-}
-- | Matches any t'MBR' that is contained within the provided one.
containedBy :: MBR -> Predicate
containedBy :: MBR -> Predicate
containedBy MBR
bx = (MBR -> Bool) -> (MBR -> Bool) -> Predicate
Predicate (MBR -> MBR -> Bool
intersectsMBR MBR
bx) (MBR -> MBR -> Bool
containsMBR MBR
bx)

{-# INLINE containedBy' #-}
-- | Matches any t'MBR' that is contained within the provided one,
--   excluding ones that touch it on one or more sides.
containedBy' :: MBR -> Predicate
containedBy' :: MBR -> Predicate
containedBy' MBR
bx = (MBR -> Bool) -> (MBR -> Bool) -> Predicate
Predicate (MBR -> MBR -> Bool
intersectsMBR MBR
bx) (MBR -> MBR -> Bool
containsMBR' MBR
bx)



instance Show a => Show (R2Tree a) where
  showsPrec :: Int -> R2Tree a -> ShowS
showsPrec = (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> R2Tree a -> ShowS
forall a.
(Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> R2Tree a -> ShowS
forall (f :: * -> *) a.
Show1 f =>
(Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> f a -> ShowS
liftShowsPrec Int -> a -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec [a] -> ShowS
forall a. Show a => [a] -> ShowS
showList

instance Show1 R2Tree where
  liftShowsPrec :: forall a.
(Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> R2Tree a -> ShowS
liftShowsPrec Int -> a -> ShowS
showsPrec_ [a] -> ShowS
showList_ Int
t R2Tree a
r =
    Bool -> ShowS -> ShowS
showParen (Int
t Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
10) (ShowS -> ShowS) -> ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$
      ((MBR, a) -> ShowS) -> [(MBR, a)] -> ShowS
forall a. (a -> ShowS) -> [a] -> ShowS
showListWith ((Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> (MBR, a) -> ShowS
forall a.
(Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> (MBR, a) -> ShowS
forall (f :: * -> *) a.
Show1 f =>
(Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> f a -> ShowS
liftShowsPrec Int -> a -> ShowS
showsPrec_ [a] -> ShowS
showList_ Int
0) ([(MBR, a)] -> ShowS) -> [(MBR, a)] -> ShowS
forall a b. (a -> b) -> a -> b
$
        (MBR -> a -> [(MBR, a)] -> [(MBR, a)])
-> [(MBR, a)] -> R2Tree a -> [(MBR, a)]
forall a b. (MBR -> a -> b -> b) -> b -> R2Tree a -> b
foldrWithKey (\MBR
k a
a -> (:) (MBR
k, a
a)) [] R2Tree a
r

instance Eq a => Eq (R2Tree a) where
  == :: R2Tree a -> R2Tree a -> Bool
(==) = (a -> a -> Bool) -> R2Tree a -> R2Tree a -> Bool
forall a b. (a -> b -> Bool) -> R2Tree a -> R2Tree b -> Bool
forall (f :: * -> *) a b.
Eq1 f =>
(a -> b -> Bool) -> f a -> f b -> Bool
liftEq a -> a -> Bool
forall a. Eq a => a -> a -> Bool
(==)

instance Eq1 R2Tree where
  liftEq :: forall a b. (a -> b -> Bool) -> R2Tree a -> R2Tree b -> Bool
liftEq a -> b -> Bool
f = R2Tree a -> R2Tree b -> Bool
go
    where
      {-# INLINE node #-}
      node :: MBR -> R2Tree a -> MBR -> R2Tree b -> Bool
node MBR
ba R2Tree a
a MBR
bb R2Tree b
b = MBR -> MBR -> Bool
eqMBR MBR
ba MBR
bb Bool -> Bool -> Bool
&& R2Tree a -> R2Tree b -> Bool
go R2Tree a
a R2Tree b
b

      {-# INLINE leaf #-}
      leaf :: MBR -> a -> MBR -> b -> Bool
leaf MBR
ba a
a MBR
bb b
b = MBR -> MBR -> Bool
eqMBR MBR
ba MBR
bb Bool -> Bool -> Bool
&& a -> b -> Bool
f a
a b
b

      go :: R2Tree a -> R2Tree b -> Bool
go R2Tree a
m R2Tree b
n =
        case R2Tree a
m of
          Node2 MBR
ba R2Tree a
a MBR
bb R2Tree a
b ->
            case R2Tree b
n of
              Node2 MBR
be R2Tree b
e MBR
bg R2Tree b
g -> MBR -> R2Tree a -> MBR -> R2Tree b -> Bool
node MBR
ba R2Tree a
a MBR
be R2Tree b
e Bool -> Bool -> Bool
&& MBR -> R2Tree a -> MBR -> R2Tree b -> Bool
node MBR
bb R2Tree a
b MBR
bg R2Tree b
g
              R2Tree b
_               -> Bool
False

          Node3 MBR
ba R2Tree a
a MBR
bb R2Tree a
b MBR
bc R2Tree a
c ->
            case R2Tree b
n of
              Node3 MBR
be R2Tree b
e MBR
bg R2Tree b
g MBR
bh R2Tree b
h -> MBR -> R2Tree a -> MBR -> R2Tree b -> Bool
node MBR
ba R2Tree a
a MBR
be R2Tree b
e Bool -> Bool -> Bool
&& MBR -> R2Tree a -> MBR -> R2Tree b -> Bool
node MBR
bb R2Tree a
b MBR
bg R2Tree b
g Bool -> Bool -> Bool
&& MBR -> R2Tree a -> MBR -> R2Tree b -> Bool
node MBR
bc R2Tree a
c MBR
bh R2Tree b
h
              R2Tree b
_                    -> Bool
False

          Node4 MBR
ba R2Tree a
a MBR
bb R2Tree a
b MBR
bc R2Tree a
c MBR
bd R2Tree a
d ->
            case R2Tree b
n of
              Node4 MBR
be R2Tree b
e MBR
bg R2Tree b
g MBR
bh R2Tree b
h MBR
bi R2Tree b
i ->
                MBR -> R2Tree a -> MBR -> R2Tree b -> Bool
node MBR
ba R2Tree a
a MBR
be R2Tree b
e Bool -> Bool -> Bool
&& MBR -> R2Tree a -> MBR -> R2Tree b -> Bool
node MBR
bb R2Tree a
b MBR
bg R2Tree b
g Bool -> Bool -> Bool
&& MBR -> R2Tree a -> MBR -> R2Tree b -> Bool
node MBR
bc R2Tree a
c MBR
bh R2Tree b
h Bool -> Bool -> Bool
&& MBR -> R2Tree a -> MBR -> R2Tree b -> Bool
node MBR
bd R2Tree a
d MBR
bi R2Tree b
i

              R2Tree b
_                         -> Bool
False

          Leaf2 MBR
ba a
a MBR
bb a
b ->
            case R2Tree b
n of
              Leaf2 MBR
be b
e MBR
bg b
g -> MBR -> a -> MBR -> b -> Bool
leaf MBR
ba a
a MBR
be b
e Bool -> Bool -> Bool
&& MBR -> a -> MBR -> b -> Bool
leaf MBR
bb a
b MBR
bg b
g
              R2Tree b
_               -> Bool
False

          Leaf3 MBR
ba a
a MBR
bb a
b MBR
bc a
c ->
            case R2Tree b
n of
              Leaf3 MBR
be b
e MBR
bg b
g MBR
bh b
h -> MBR -> a -> MBR -> b -> Bool
leaf MBR
ba a
a MBR
be b
e Bool -> Bool -> Bool
&& MBR -> a -> MBR -> b -> Bool
leaf MBR
bb a
b MBR
bg b
g Bool -> Bool -> Bool
&& MBR -> a -> MBR -> b -> Bool
leaf MBR
bc a
c MBR
bh b
h
              R2Tree b
_                    -> Bool
False

          Leaf4 MBR
ba a
a MBR
bb a
b MBR
bc a
c MBR
bd a
d ->
            case R2Tree b
n of
              Leaf4 MBR
be b
e MBR
bg b
g MBR
bh b
h MBR
bi b
i ->
                MBR -> a -> MBR -> b -> Bool
leaf MBR
ba a
a MBR
be b
e Bool -> Bool -> Bool
&& MBR -> a -> MBR -> b -> Bool
leaf MBR
bb a
b MBR
bg b
g Bool -> Bool -> Bool
&& MBR -> a -> MBR -> b -> Bool
leaf MBR
bc a
c MBR
bh b
h Bool -> Bool -> Bool
&& MBR -> a -> MBR -> b -> Bool
leaf MBR
bd a
d MBR
bi b
i

              R2Tree b
_                     -> Bool
False

          Leaf1 MBR
ba a
a ->
            case R2Tree b
n of
              Leaf1 MBR
bb b
b -> MBR -> MBR -> Bool
eqMBR MBR
ba MBR
bb Bool -> Bool -> Bool
&& a -> b -> Bool
f a
a b
b
              R2Tree b
_          -> Bool
False

          R2Tree a
Empty      ->
            case R2Tree b
n of
              R2Tree b
Empty -> Bool
True
              R2Tree b
_     -> Bool
False



instance NFData a => NFData (R2Tree a) where
  rnf :: R2Tree a -> ()
rnf = (a -> ()) -> R2Tree a -> ()
forall a. (a -> ()) -> R2Tree a -> ()
forall (f :: * -> *) a. NFData1 f => (a -> ()) -> f a -> ()
liftRnf a -> ()
forall a. NFData a => a -> ()
rnf

instance NFData1 R2Tree where
  liftRnf :: forall a. (a -> ()) -> R2Tree a -> ()
liftRnf a -> ()
f = R2Tree a -> ()
go
    where
      go :: R2Tree a -> ()
go R2Tree a
n =
        case R2Tree a
n of
          Node2 MBR
_ R2Tree a
a MBR
_ R2Tree a
b         -> R2Tree a -> ()
go R2Tree a
a () -> () -> ()
forall a b. a -> b -> b
`seq` R2Tree a -> ()
go R2Tree a
b
          Node3 MBR
_ R2Tree a
a MBR
_ R2Tree a
b MBR
_ R2Tree a
c     -> R2Tree a -> ()
go R2Tree a
a () -> () -> ()
forall a b. a -> b -> b
`seq` R2Tree a -> ()
go R2Tree a
b () -> () -> ()
forall a b. a -> b -> b
`seq` R2Tree a -> ()
go R2Tree a
c
          Node4 MBR
_ R2Tree a
a MBR
_ R2Tree a
b MBR
_ R2Tree a
c MBR
_ R2Tree a
d -> R2Tree a -> ()
go R2Tree a
a () -> () -> ()
forall a b. a -> b -> b
`seq` R2Tree a -> ()
go R2Tree a
b () -> () -> ()
forall a b. a -> b -> b
`seq` R2Tree a -> ()
go R2Tree a
c () -> () -> ()
forall a b. a -> b -> b
`seq` R2Tree a -> ()
go R2Tree a
d

          Leaf2 MBR
_ a
a MBR
_ a
b         -> a -> ()
f a
a () -> () -> ()
forall a b. a -> b -> b
`seq` a -> ()
f a
b
          Leaf3 MBR
_ a
a MBR
_ a
b MBR
_ a
c     -> a -> ()
f a
a () -> () -> ()
forall a b. a -> b -> b
`seq` a -> ()
f a
b () -> () -> ()
forall a b. a -> b -> b
`seq` a -> ()
f a
c
          Leaf4 MBR
_ a
a MBR
_ a
b MBR
_ a
c MBR
_ a
d -> a -> ()
f a
a () -> () -> ()
forall a b. a -> b -> b
`seq` a -> ()
f a
b () -> () -> ()
forall a b. a -> b -> b
`seq` a -> ()
f a
c () -> () -> ()
forall a b. a -> b -> b
`seq` a -> ()
f a
d

          Leaf1 MBR
_ a
a             -> a -> ()
f a
a
          R2Tree a
Empty                 -> ()



-- | Uses 'Data.R2Tree.Double.map'.
instance Functor R2Tree where
  fmap :: forall a b. (a -> b) -> R2Tree a -> R2Tree b
fmap = (a -> b) -> R2Tree a -> R2Tree b
forall a b. (a -> b) -> R2Tree a -> R2Tree b
Data.R2Tree.Double.Internal.map

instance Foldable R2Tree where
  foldl :: forall b a. (b -> a -> b) -> b -> R2Tree a -> b
foldl = (b -> a -> b) -> b -> R2Tree a -> b
forall b a. (b -> a -> b) -> b -> R2Tree a -> b
Data.R2Tree.Double.Internal.foldl

  foldr :: forall a b. (a -> b -> b) -> b -> R2Tree a -> b
foldr = (a -> b -> b) -> b -> R2Tree a -> b
forall a b. (a -> b -> b) -> b -> R2Tree a -> b
Data.R2Tree.Double.Internal.foldr

  foldMap :: forall m a. Monoid m => (a -> m) -> R2Tree a -> m
foldMap = (a -> m) -> R2Tree a -> m
forall m a. Monoid m => (a -> m) -> R2Tree a -> m
Data.R2Tree.Double.Internal.foldMap

  foldl' :: forall b a. (b -> a -> b) -> b -> R2Tree a -> b
foldl' = (b -> a -> b) -> b -> R2Tree a -> b
forall b a. (b -> a -> b) -> b -> R2Tree a -> b
Data.R2Tree.Double.Internal.foldl'

  foldr' :: forall a b. (a -> b -> b) -> b -> R2Tree a -> b
foldr' = (a -> b -> b) -> b -> R2Tree a -> b
forall a b. (a -> b -> b) -> b -> R2Tree a -> b
Data.R2Tree.Double.Internal.foldr'

  null :: forall a. R2Tree a -> Bool
null = R2Tree a -> Bool
forall a. R2Tree a -> Bool
Data.R2Tree.Double.Internal.null

  length :: forall a. R2Tree a -> Int
length = R2Tree a -> Int
forall a. R2Tree a -> Int
size


instance Traversable R2Tree where
  traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> R2Tree a -> f (R2Tree b)
traverse = (a -> f b) -> R2Tree a -> f (R2Tree b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> R2Tree a -> f (R2Tree b)
Data.R2Tree.Double.Internal.traverse



-- | Spine-strict two-dimensional R-tree.
data R2Tree a = Node2 {-# UNPACK #-} !MBR !(R2Tree a) {-# UNPACK #-} !MBR !(R2Tree a)
             | Node3 {-# UNPACK #-} !MBR !(R2Tree a) {-# UNPACK #-} !MBR !(R2Tree a) {-# UNPACK #-} !MBR !(R2Tree a)
             | Node4 {-# UNPACK #-} !MBR !(R2Tree a) {-# UNPACK #-} !MBR !(R2Tree a) {-# UNPACK #-} !MBR !(R2Tree a) {-# UNPACK #-} !MBR !(R2Tree a)

             | Leaf2 {-# UNPACK #-} !MBR a {-# UNPACK #-} !MBR a
             | Leaf3 {-# UNPACK #-} !MBR a {-# UNPACK #-} !MBR a {-# UNPACK #-} !MBR a
             | Leaf4 {-# UNPACK #-} !MBR a {-# UNPACK #-} !MBR a {-# UNPACK #-} !MBR a {-# UNPACK #-} !MBR a

               -- | Invariant: only allowed as the root node.
             | Leaf1 {-# UNPACK #-} !MBR a

               -- | Invariant: only allowed as the root node.
             | Empty



-- | \(\mathcal{O}(1)\).
--   Check if the tree is empty.
null :: R2Tree a -> Bool
null :: forall a. R2Tree a -> Bool
null R2Tree a
Empty = Bool
True
null R2Tree a
_     = Bool
False

-- | \(\mathcal{O}(n)\).
--   Calculate the number of elements stored in the tree.
--   The returned number is guaranteed to be non-negative.
size :: R2Tree a -> Int
size :: forall a. R2Tree a -> Int
size = R2Tree a -> Int
forall {a} {a}. Num a => R2Tree a -> a
go
  where
    go :: R2Tree a -> a
go R2Tree a
n =
      case R2Tree a
n of
        Node2 MBR
_ R2Tree a
a MBR
_ R2Tree a
b         -> let !w :: a
w = R2Tree a -> a
go R2Tree a
a
                                     !x :: a
x = R2Tree a -> a
go R2Tree a
b

                                 in a
w a -> a -> a
forall a. Num a => a -> a -> a
+ a
x

        Node3 MBR
_ R2Tree a
a MBR
_ R2Tree a
b MBR
_ R2Tree a
c     -> let !w :: a
w = R2Tree a -> a
go R2Tree a
a
                                     !x :: a
x = R2Tree a -> a
go R2Tree a
b
                                     !y :: a
y = R2Tree a -> a
go R2Tree a
c

                                 in a
w a -> a -> a
forall a. Num a => a -> a -> a
+ a
x a -> a -> a
forall a. Num a => a -> a -> a
+ a
y

        Node4 MBR
_ R2Tree a
a MBR
_ R2Tree a
b MBR
_ R2Tree a
c MBR
_ R2Tree a
d -> let !w :: a
w = R2Tree a -> a
go R2Tree a
a
                                     !x :: a
x = R2Tree a -> a
go R2Tree a
b
                                     !y :: a
y = R2Tree a -> a
go R2Tree a
c
                                     !z :: a
z = R2Tree a -> a
go R2Tree a
d

                                 in a
w a -> a -> a
forall a. Num a => a -> a -> a
+ a
x a -> a -> a
forall a. Num a => a -> a -> a
+ a
y a -> a -> a
forall a. Num a => a -> a -> a
+ a
z

        Leaf2 MBR
_ a
_ MBR
_ a
_         -> a
2
        Leaf3 MBR
_ a
_ MBR
_ a
_ MBR
_ a
_     -> a
3
        Leaf4 MBR
_ a
_ MBR
_ a
_ MBR
_ a
_ MBR
_ a
_ -> a
4

        Leaf1 MBR
_ a
_             -> a
1
        R2Tree a
Empty                 -> a
0



-- | \(\mathcal{O}(n)\).
--   Map a function over all values.
map :: (a -> b) -> R2Tree a -> R2Tree b
map :: forall a b. (a -> b) -> R2Tree a -> R2Tree b
map a -> b
f = R2Tree a -> R2Tree b
go
  where
    go :: R2Tree a -> R2Tree b
go R2Tree a
n =
      case R2Tree a
n of
        Node2 MBR
ba R2Tree a
a MBR
bb R2Tree a
b           ->
          MBR -> R2Tree b -> MBR -> R2Tree b -> R2Tree b
forall a. MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node2 MBR
ba (R2Tree a -> R2Tree b
go R2Tree a
a) MBR
bb (R2Tree a -> R2Tree b
go R2Tree a
b)

        Node3 MBR
ba R2Tree a
a MBR
bb R2Tree a
b MBR
bc R2Tree a
c      ->
          MBR -> R2Tree b -> MBR -> R2Tree b -> MBR -> R2Tree b -> R2Tree b
forall a.
MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node3 MBR
ba (R2Tree a -> R2Tree b
go R2Tree a
a) MBR
bb (R2Tree a -> R2Tree b
go R2Tree a
b) MBR
bc (R2Tree a -> R2Tree b
go R2Tree a
c)

        Node4 MBR
ba R2Tree a
a MBR
bb R2Tree a
b MBR
bc R2Tree a
c MBR
bd R2Tree a
d ->
          MBR
-> R2Tree b
-> MBR
-> R2Tree b
-> MBR
-> R2Tree b
-> MBR
-> R2Tree b
-> R2Tree b
forall a.
MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> R2Tree a
Node4 MBR
ba (R2Tree a -> R2Tree b
go R2Tree a
a) MBR
bb (R2Tree a -> R2Tree b
go R2Tree a
b) MBR
bc (R2Tree a -> R2Tree b
go R2Tree a
c) MBR
bd (R2Tree a -> R2Tree b
go R2Tree a
d)

        Leaf2 MBR
ba a
a MBR
bb a
b           ->
          MBR -> b -> MBR -> b -> R2Tree b
forall a. MBR -> a -> MBR -> a -> R2Tree a
Leaf2 MBR
ba (a -> b
f a
a) MBR
bb (a -> b
f a
b)

        Leaf3 MBR
ba a
a MBR
bb a
b MBR
bc a
c      ->
          MBR -> b -> MBR -> b -> MBR -> b -> R2Tree b
forall a. MBR -> a -> MBR -> a -> MBR -> a -> R2Tree a
Leaf3 MBR
ba (a -> b
f a
a) MBR
bb (a -> b
f a
b) MBR
bc (a -> b
f a
c)

        Leaf4 MBR
ba a
a MBR
bb a
b MBR
bc a
c MBR
bd a
d ->
          MBR -> b -> MBR -> b -> MBR -> b -> MBR -> b -> R2Tree b
forall a. MBR -> a -> MBR -> a -> MBR -> a -> MBR -> a -> R2Tree a
Leaf4 MBR
ba (a -> b
f a
a) MBR
bb (a -> b
f a
b) MBR
bc (a -> b
f a
c) MBR
bd (a -> b
f a
d)

        Leaf1 MBR
ba a
a                ->
          MBR -> b -> R2Tree b
forall a. MBR -> a -> R2Tree a
Leaf1 MBR
ba (a -> b
f a
a)

        R2Tree a
Empty                     -> R2Tree b
forall a. R2Tree a
Empty

-- | \(\mathcal{O}(n)\).
--   Map a function over all values and evaluate the results to WHNF.
map' :: (a -> b) -> R2Tree a -> R2Tree b
map' :: forall a b. (a -> b) -> R2Tree a -> R2Tree b
map' a -> b
f = R2Tree a -> R2Tree b
go
  where
    go :: R2Tree a -> R2Tree b
go R2Tree a
n =
      case R2Tree a
n of
        Node2 MBR
ba R2Tree a
a MBR
bb R2Tree a
b           ->
          MBR -> R2Tree b -> MBR -> R2Tree b -> R2Tree b
forall a. MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node2 MBR
ba (R2Tree a -> R2Tree b
go R2Tree a
a) MBR
bb (R2Tree a -> R2Tree b
go R2Tree a
b)

        Node3 MBR
ba R2Tree a
a MBR
bb R2Tree a
b MBR
bc R2Tree a
c      ->
          MBR -> R2Tree b -> MBR -> R2Tree b -> MBR -> R2Tree b -> R2Tree b
forall a.
MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node3 MBR
ba (R2Tree a -> R2Tree b
go R2Tree a
a) MBR
bb (R2Tree a -> R2Tree b
go R2Tree a
b) MBR
bc (R2Tree a -> R2Tree b
go R2Tree a
c)

        Node4 MBR
ba R2Tree a
a MBR
bb R2Tree a
b MBR
bc R2Tree a
c MBR
bd R2Tree a
d ->
          MBR
-> R2Tree b
-> MBR
-> R2Tree b
-> MBR
-> R2Tree b
-> MBR
-> R2Tree b
-> R2Tree b
forall a.
MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> R2Tree a
Node4 MBR
ba (R2Tree a -> R2Tree b
go R2Tree a
a) MBR
bb (R2Tree a -> R2Tree b
go R2Tree a
b) MBR
bc (R2Tree a -> R2Tree b
go R2Tree a
c) MBR
bd (R2Tree a -> R2Tree b
go R2Tree a
d)

        Leaf2 MBR
ba a
a MBR
bb a
b           ->
          let !a' :: b
a' = a -> b
f a
a
              !b' :: b
b' = a -> b
f a
b

          in MBR -> b -> MBR -> b -> R2Tree b
forall a. MBR -> a -> MBR -> a -> R2Tree a
Leaf2 MBR
ba b
a' MBR
bb b
b'

        Leaf3 MBR
ba a
a MBR
bb a
b MBR
bc a
c      ->
          let !a' :: b
a' = a -> b
f a
a
              !b' :: b
b' = a -> b
f a
b
              !c' :: b
c' = a -> b
f a
c

          in MBR -> b -> MBR -> b -> MBR -> b -> R2Tree b
forall a. MBR -> a -> MBR -> a -> MBR -> a -> R2Tree a
Leaf3 MBR
ba b
a' MBR
bb b
b' MBR
bc b
c'

        Leaf4 MBR
ba a
a MBR
bb a
b MBR
bc a
c MBR
bd a
d ->
          let !a' :: b
a' = a -> b
f a
a
              !b' :: b
b' = a -> b
f a
b
              !c' :: b
c' = a -> b
f a
c
              !d' :: b
d' = a -> b
f a
d

          in MBR -> b -> MBR -> b -> MBR -> b -> MBR -> b -> R2Tree b
forall a. MBR -> a -> MBR -> a -> MBR -> a -> MBR -> a -> R2Tree a
Leaf4 MBR
ba b
a' MBR
bb b
b' MBR
bc b
c' MBR
bd b
d'

        Leaf1 MBR
ba a
a                ->
          MBR -> b -> R2Tree b
forall a. MBR -> a -> R2Tree a
Leaf1 MBR
ba (b -> R2Tree b) -> b -> R2Tree b
forall a b. (a -> b) -> a -> b
$! a -> b
f a
a
        
        R2Tree a
Empty                     -> R2Tree b
forall a. R2Tree a
Empty


-- | \(\mathcal{O}(n)\).
--   Map a function over all t'MBR's and their respective values.
mapWithKey :: (MBR -> a -> b) -> R2Tree a -> R2Tree b
mapWithKey :: forall a b. (MBR -> a -> b) -> R2Tree a -> R2Tree b
mapWithKey MBR -> a -> b
f = R2Tree a -> R2Tree b
go
  where
    go :: R2Tree a -> R2Tree b
go R2Tree a
n =
      case R2Tree a
n of
        Node2 MBR
ba R2Tree a
a MBR
bb R2Tree a
b           ->
          MBR -> R2Tree b -> MBR -> R2Tree b -> R2Tree b
forall a. MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node2 MBR
ba (R2Tree a -> R2Tree b
go R2Tree a
a) MBR
bb (R2Tree a -> R2Tree b
go R2Tree a
b)

        Node3 MBR
ba R2Tree a
a MBR
bb R2Tree a
b MBR
bc R2Tree a
c      ->
          MBR -> R2Tree b -> MBR -> R2Tree b -> MBR -> R2Tree b -> R2Tree b
forall a.
MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node3 MBR
ba (R2Tree a -> R2Tree b
go R2Tree a
a) MBR
bb (R2Tree a -> R2Tree b
go R2Tree a
b) MBR
bc (R2Tree a -> R2Tree b
go R2Tree a
c)

        Node4 MBR
ba R2Tree a
a MBR
bb R2Tree a
b MBR
bc R2Tree a
c MBR
bd R2Tree a
d ->
          MBR
-> R2Tree b
-> MBR
-> R2Tree b
-> MBR
-> R2Tree b
-> MBR
-> R2Tree b
-> R2Tree b
forall a.
MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> R2Tree a
Node4 MBR
ba (R2Tree a -> R2Tree b
go R2Tree a
a) MBR
bb (R2Tree a -> R2Tree b
go R2Tree a
b) MBR
bc (R2Tree a -> R2Tree b
go R2Tree a
c) MBR
bd (R2Tree a -> R2Tree b
go R2Tree a
d)

        Leaf2 MBR
ba a
a MBR
bb a
b           ->
          MBR -> b -> MBR -> b -> R2Tree b
forall a. MBR -> a -> MBR -> a -> R2Tree a
Leaf2 MBR
ba (MBR -> a -> b
f MBR
ba a
a) MBR
bb (MBR -> a -> b
f MBR
bb a
b)

        Leaf3 MBR
ba a
a MBR
bb a
b MBR
bc a
c      ->
          MBR -> b -> MBR -> b -> MBR -> b -> R2Tree b
forall a. MBR -> a -> MBR -> a -> MBR -> a -> R2Tree a
Leaf3 MBR
ba (MBR -> a -> b
f MBR
ba a
a) MBR
bb (MBR -> a -> b
f MBR
bb a
b) MBR
bc (MBR -> a -> b
f MBR
bc a
c)

        Leaf4 MBR
ba a
a MBR
bb a
b MBR
bc a
c MBR
bd a
d ->
          MBR -> b -> MBR -> b -> MBR -> b -> MBR -> b -> R2Tree b
forall a. MBR -> a -> MBR -> a -> MBR -> a -> MBR -> a -> R2Tree a
Leaf4 MBR
ba (MBR -> a -> b
f MBR
ba a
a) MBR
bb (MBR -> a -> b
f MBR
bb a
b) MBR
bc (MBR -> a -> b
f MBR
bc a
c) MBR
bd (MBR -> a -> b
f MBR
bd a
d)

        Leaf1 MBR
ba a
a                ->
          MBR -> b -> R2Tree b
forall a. MBR -> a -> R2Tree a
Leaf1 MBR
ba (MBR -> a -> b
f MBR
ba a
a)

        R2Tree a
Empty                     -> R2Tree b
forall a. R2Tree a
Empty

-- | \(\mathcal{O}(n)\).
--   Map a function over all t'MBR's and their respective values
--   and evaluate the results to WHNF.
mapWithKey' :: (MBR -> a -> b) -> R2Tree a -> R2Tree b
mapWithKey' :: forall a b. (MBR -> a -> b) -> R2Tree a -> R2Tree b
mapWithKey' MBR -> a -> b
f = R2Tree a -> R2Tree b
go
  where
    go :: R2Tree a -> R2Tree b
go R2Tree a
n =
      case R2Tree a
n of
        Node2 MBR
ba R2Tree a
a MBR
bb R2Tree a
b           ->
          MBR -> R2Tree b -> MBR -> R2Tree b -> R2Tree b
forall a. MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node2 MBR
ba (R2Tree a -> R2Tree b
go R2Tree a
a) MBR
bb (R2Tree a -> R2Tree b
go R2Tree a
b)

        Node3 MBR
ba R2Tree a
a MBR
bb R2Tree a
b MBR
bc R2Tree a
c      ->
          MBR -> R2Tree b -> MBR -> R2Tree b -> MBR -> R2Tree b -> R2Tree b
forall a.
MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node3 MBR
ba (R2Tree a -> R2Tree b
go R2Tree a
a) MBR
bb (R2Tree a -> R2Tree b
go R2Tree a
b) MBR
bc (R2Tree a -> R2Tree b
go R2Tree a
c)

        Node4 MBR
ba R2Tree a
a MBR
bb R2Tree a
b MBR
bc R2Tree a
c MBR
bd R2Tree a
d ->
          MBR
-> R2Tree b
-> MBR
-> R2Tree b
-> MBR
-> R2Tree b
-> MBR
-> R2Tree b
-> R2Tree b
forall a.
MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> R2Tree a
Node4 MBR
ba (R2Tree a -> R2Tree b
go R2Tree a
a) MBR
bb (R2Tree a -> R2Tree b
go R2Tree a
b) MBR
bc (R2Tree a -> R2Tree b
go R2Tree a
c) MBR
bd (R2Tree a -> R2Tree b
go R2Tree a
d)

        Leaf2 MBR
ba a
a MBR
bb a
b           ->
          let !a' :: b
a' = MBR -> a -> b
f MBR
ba a
a
              !b' :: b
b' = MBR -> a -> b
f MBR
bb a
b

          in MBR -> b -> MBR -> b -> R2Tree b
forall a. MBR -> a -> MBR -> a -> R2Tree a
Leaf2 MBR
ba b
a' MBR
bb b
b'

        Leaf3 MBR
ba a
a MBR
bb a
b MBR
bc a
c      ->
          let !a' :: b
a' = MBR -> a -> b
f MBR
ba a
a
              !b' :: b
b' = MBR -> a -> b
f MBR
bb a
b
              !c' :: b
c' = MBR -> a -> b
f MBR
bc a
c

          in MBR -> b -> MBR -> b -> MBR -> b -> R2Tree b
forall a. MBR -> a -> MBR -> a -> MBR -> a -> R2Tree a
Leaf3 MBR
ba b
a' MBR
bb b
b' MBR
bc b
c'

        Leaf4 MBR
ba a
a MBR
bb a
b MBR
bc a
c MBR
bd a
d ->
          let !a' :: b
a' = MBR -> a -> b
f MBR
ba a
a
              !b' :: b
b' = MBR -> a -> b
f MBR
bb a
b
              !c' :: b
c' = MBR -> a -> b
f MBR
bc a
c
              !d' :: b
d' = MBR -> a -> b
f MBR
bd a
d

          in MBR -> b -> MBR -> b -> MBR -> b -> MBR -> b -> R2Tree b
forall a. MBR -> a -> MBR -> a -> MBR -> a -> MBR -> a -> R2Tree a
Leaf4 MBR
ba b
a' MBR
bb b
b' MBR
bc b
c' MBR
bd b
d'

        Leaf1 MBR
ba a
a                ->
          MBR -> b -> R2Tree b
forall a. MBR -> a -> R2Tree a
Leaf1 MBR
ba (b -> R2Tree b) -> b -> R2Tree b
forall a b. (a -> b) -> a -> b
$! MBR -> a -> b
f MBR
ba a
a

        R2Tree a
Empty                     -> R2Tree b
forall a. R2Tree a
Empty



{-# INLINE adjustRangeWithKey #-}
-- | \(\mathcal{O}(\log n + n_I)\).
--   Map a function over t'MBR's that match the 'Predicate' and their respective values.
adjustRangeWithKey :: Predicate -> (MBR -> a -> a) -> R2Tree a -> R2Tree a
adjustRangeWithKey :: forall a. Predicate -> (MBR -> a -> a) -> R2Tree a -> R2Tree a
adjustRangeWithKey (Predicate MBR -> Bool
nodePred MBR -> Bool
leafPred) MBR -> a -> a
f = R2Tree a -> R2Tree a
go
  where
    {-# INLINE node #-}
    node :: MBR -> R2Tree a -> R2Tree a
node MBR
bx R2Tree a
x
      | MBR -> Bool
nodePred MBR
bx = R2Tree a -> R2Tree a
go R2Tree a
x
      | Bool
otherwise   = R2Tree a
x

    {-# INLINE leaf #-}
    leaf :: MBR -> a -> a
leaf MBR
bx a
x
      | MBR -> Bool
leafPred MBR
bx = MBR -> a -> a
f MBR
bx a
x
      | Bool
otherwise   = a
x

    go :: R2Tree a -> R2Tree a
go R2Tree a
n =
      case R2Tree a
n of
        Node2 MBR
ba R2Tree a
a MBR
bb R2Tree a
b           ->
          MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
forall a. MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node2 MBR
ba (MBR -> R2Tree a -> R2Tree a
node MBR
ba R2Tree a
a) MBR
bb (MBR -> R2Tree a -> R2Tree a
node MBR
bb R2Tree a
b)

        Node3 MBR
ba R2Tree a
a MBR
bb R2Tree a
b MBR
bc R2Tree a
c      ->
          MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
forall a.
MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node3 MBR
ba (MBR -> R2Tree a -> R2Tree a
node MBR
ba R2Tree a
a) MBR
bb (MBR -> R2Tree a -> R2Tree a
node MBR
bb R2Tree a
b) MBR
bc (MBR -> R2Tree a -> R2Tree a
node MBR
bc R2Tree a
c)

        Node4 MBR
ba R2Tree a
a MBR
bb R2Tree a
b MBR
bc R2Tree a
c MBR
bd R2Tree a
d ->
          MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> R2Tree a
forall a.
MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> R2Tree a
Node4 MBR
ba (MBR -> R2Tree a -> R2Tree a
node MBR
ba R2Tree a
a) MBR
bb (MBR -> R2Tree a -> R2Tree a
node MBR
bb R2Tree a
b) MBR
bc (MBR -> R2Tree a -> R2Tree a
node MBR
bc R2Tree a
c) MBR
bd (MBR -> R2Tree a -> R2Tree a
node MBR
bd R2Tree a
d)

        Leaf2 MBR
ba a
a MBR
bb a
b           ->
          MBR -> a -> MBR -> a -> R2Tree a
forall a. MBR -> a -> MBR -> a -> R2Tree a
Leaf2 MBR
ba (MBR -> a -> a
leaf MBR
ba a
a) MBR
bb (MBR -> a -> a
leaf MBR
bb a
b)

        Leaf3 MBR
ba a
a MBR
bb a
b MBR
bc a
c      ->
          MBR -> a -> MBR -> a -> MBR -> a -> R2Tree a
forall a. MBR -> a -> MBR -> a -> MBR -> a -> R2Tree a
Leaf3 MBR
ba (MBR -> a -> a
leaf MBR
ba a
a) MBR
bb (MBR -> a -> a
leaf MBR
bb a
b) MBR
bc (MBR -> a -> a
leaf MBR
bc a
c)

        Leaf4 MBR
ba a
a MBR
bb a
b MBR
bc a
c MBR
bd a
d ->
          MBR -> a -> MBR -> a -> MBR -> a -> MBR -> a -> R2Tree a
forall a. MBR -> a -> MBR -> a -> MBR -> a -> MBR -> a -> R2Tree a
Leaf4 MBR
ba (MBR -> a -> a
leaf MBR
ba a
a) MBR
bb (MBR -> a -> a
leaf MBR
bb a
b) MBR
bc (MBR -> a -> a
leaf MBR
bc a
c) MBR
bd (MBR -> a -> a
leaf MBR
bd a
d)

        Leaf1 MBR
ba a
a                ->
          MBR -> a -> R2Tree a
forall a. MBR -> a -> R2Tree a
Leaf1 MBR
ba (MBR -> a -> a
leaf MBR
ba a
a)

        R2Tree a
Empty                     -> R2Tree a
forall a. R2Tree a
Empty

{-# INLINE adjustRangeWithKey' #-}
-- | \(\mathcal{O}(\log n + n_I)\).
--   Map a function over t'MBR's that match the 'Predicate' and their respective values
--   and evaluate the results to WHNF.
adjustRangeWithKey' :: Predicate -> (MBR -> a -> a) -> R2Tree a -> R2Tree a
adjustRangeWithKey' :: forall a. Predicate -> (MBR -> a -> a) -> R2Tree a -> R2Tree a
adjustRangeWithKey' (Predicate MBR -> Bool
nodePred MBR -> Bool
leafPred) MBR -> a -> a
f = R2Tree a -> R2Tree a
go
  where
    {-# INLINE node #-}
    node :: MBR -> R2Tree a -> R2Tree a
node MBR
bx R2Tree a
x
      | MBR -> Bool
nodePred MBR
bx = R2Tree a -> R2Tree a
go R2Tree a
x
      | Bool
otherwise   = R2Tree a
x

    {-# INLINE leaf #-}
    leaf :: MBR -> a -> a
leaf MBR
bx a
x
      | MBR -> Bool
leafPred MBR
bx = MBR -> a -> a
f MBR
bx a
x
      | Bool
otherwise   = a
x

    go :: R2Tree a -> R2Tree a
go R2Tree a
n =
      case R2Tree a
n of
        Node2 MBR
ba R2Tree a
a MBR
bb R2Tree a
b           ->
          MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
forall a. MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node2 MBR
ba (MBR -> R2Tree a -> R2Tree a
node MBR
ba R2Tree a
a) MBR
bb (MBR -> R2Tree a -> R2Tree a
node MBR
bb R2Tree a
b)

        Node3 MBR
ba R2Tree a
a MBR
bb R2Tree a
b MBR
bc R2Tree a
c      ->
          MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
forall a.
MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node3 MBR
ba (MBR -> R2Tree a -> R2Tree a
node MBR
ba R2Tree a
a) MBR
bb (MBR -> R2Tree a -> R2Tree a
node MBR
bb R2Tree a
b) MBR
bc (MBR -> R2Tree a -> R2Tree a
node MBR
bc R2Tree a
c)

        Node4 MBR
ba R2Tree a
a MBR
bb R2Tree a
b MBR
bc R2Tree a
c MBR
bd R2Tree a
d ->
          MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> R2Tree a
forall a.
MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> R2Tree a
Node4 MBR
ba (MBR -> R2Tree a -> R2Tree a
node MBR
ba R2Tree a
a) MBR
bb (MBR -> R2Tree a -> R2Tree a
node MBR
bb R2Tree a
b) MBR
bc (MBR -> R2Tree a -> R2Tree a
node MBR
bc R2Tree a
c) MBR
bd (MBR -> R2Tree a -> R2Tree a
node MBR
bd R2Tree a
d)

        Leaf2 MBR
ba a
a MBR
bb a
b           ->
          let !a' :: a
a' = MBR -> a -> a
leaf MBR
ba a
a
              !b' :: a
b' = MBR -> a -> a
leaf MBR
bb a
b

          in MBR -> a -> MBR -> a -> R2Tree a
forall a. MBR -> a -> MBR -> a -> R2Tree a
Leaf2 MBR
ba a
a' MBR
bb a
b'

        Leaf3 MBR
ba a
a MBR
bb a
b MBR
bc a
c      ->
          let !a' :: a
a' = MBR -> a -> a
leaf MBR
ba a
a
              !b' :: a
b' = MBR -> a -> a
leaf MBR
bb a
b
              !c' :: a
c' = MBR -> a -> a
leaf MBR
bc a
c

          in MBR -> a -> MBR -> a -> MBR -> a -> R2Tree a
forall a. MBR -> a -> MBR -> a -> MBR -> a -> R2Tree a
Leaf3 MBR
ba a
a' MBR
bb a
b' MBR
bc a
c'

        Leaf4 MBR
ba a
a MBR
bb a
b MBR
bc a
c MBR
bd a
d ->
          let !a' :: a
a' = MBR -> a -> a
leaf MBR
ba a
a
              !b' :: a
b' = MBR -> a -> a
leaf MBR
bb a
b
              !c' :: a
c' = MBR -> a -> a
leaf MBR
bc a
c
              !d' :: a
d' = MBR -> a -> a
leaf MBR
bd a
d

          in MBR -> a -> MBR -> a -> MBR -> a -> MBR -> a -> R2Tree a
forall a. MBR -> a -> MBR -> a -> MBR -> a -> MBR -> a -> R2Tree a
Leaf4 MBR
ba a
a' MBR
bb a
b' MBR
bc a
c' MBR
bd a
d'

        Leaf1 MBR
ba a
a                ->
          MBR -> a -> R2Tree a
forall a. MBR -> a -> R2Tree a
Leaf1 MBR
ba (a -> R2Tree a) -> a -> R2Tree a
forall a b. (a -> b) -> a -> b
$! MBR -> a -> a
leaf MBR
ba a
a

        R2Tree a
Empty                     -> R2Tree a
forall a. R2Tree a
Empty



-- | \(\mathcal{O}(n_R)\).
--   Fold left-to-right over all values.
foldl :: (b -> a -> b) -> b -> R2Tree a -> b
foldl :: forall b a. (b -> a -> b) -> b -> R2Tree a -> b
foldl b -> a -> b
f = b -> R2Tree a -> b
go
  where
    go :: b -> R2Tree a -> b
go b
z R2Tree a
n =
      case R2Tree a
n of
        Node2 MBR
_ R2Tree a
a MBR
_ R2Tree a
b         ->         b -> R2Tree a -> b
go (b -> R2Tree a -> b
go b
z R2Tree a
a) R2Tree a
b
        Node3 MBR
_ R2Tree a
a MBR
_ R2Tree a
b MBR
_ R2Tree a
c     ->     b -> R2Tree a -> b
go (b -> R2Tree a -> b
go (b -> R2Tree a -> b
go b
z R2Tree a
a) R2Tree a
b) R2Tree a
c
        Node4 MBR
_ R2Tree a
a MBR
_ R2Tree a
b MBR
_ R2Tree a
c MBR
_ R2Tree a
d -> b -> R2Tree a -> b
go (b -> R2Tree a -> b
go (b -> R2Tree a -> b
go (b -> R2Tree a -> b
go b
z R2Tree a
a) R2Tree a
b) R2Tree a
c) R2Tree a
d

        Leaf2 MBR
_ a
a MBR
_ a
b         ->       b -> a -> b
f (b -> a -> b
f b
z a
a) a
b
        Leaf3 MBR
_ a
a MBR
_ a
b MBR
_ a
c     ->    b -> a -> b
f (b -> a -> b
f (b -> a -> b
f b
z a
a) a
b) a
c
        Leaf4 MBR
_ a
a MBR
_ a
b MBR
_ a
c MBR
_ a
d -> b -> a -> b
f (b -> a -> b
f (b -> a -> b
f (b -> a -> b
f b
z a
a) a
b) a
c) a
d

        Leaf1 MBR
_ a
a             -> b -> a -> b
f b
z a
a
        R2Tree a
Empty                 -> b
z

-- | \(\mathcal{O}(n)\).
--   Fold left-to-right over all values, applying the operator function strictly.
foldl' :: (b -> a -> b) -> b -> R2Tree a -> b
foldl' :: forall b a. (b -> a -> b) -> b -> R2Tree a -> b
foldl' b -> a -> b
f = b -> R2Tree a -> b
go
  where
    {-# INLINE leaf #-}
    leaf :: b -> a -> b
leaf !b
z a
x = b -> a -> b
f b
z a
x

    go :: b -> R2Tree a -> b
go !b
z R2Tree a
n =
      case R2Tree a
n of
        Node2 MBR
_ R2Tree a
a MBR
_ R2Tree a
b         ->         b -> R2Tree a -> b
go (b -> R2Tree a -> b
go b
z R2Tree a
a) R2Tree a
b
        Node3 MBR
_ R2Tree a
a MBR
_ R2Tree a
b MBR
_ R2Tree a
c     ->     b -> R2Tree a -> b
go (b -> R2Tree a -> b
go (b -> R2Tree a -> b
go b
z R2Tree a
a) R2Tree a
b) R2Tree a
c
        Node4 MBR
_ R2Tree a
a MBR
_ R2Tree a
b MBR
_ R2Tree a
c MBR
_ R2Tree a
d -> b -> R2Tree a -> b
go (b -> R2Tree a -> b
go (b -> R2Tree a -> b
go (b -> R2Tree a -> b
go b
z R2Tree a
a) R2Tree a
b) R2Tree a
c) R2Tree a
d

        Leaf2 MBR
_ a
a MBR
_ a
b         ->             b -> a -> b
leaf (b -> a -> b
leaf b
z a
a) a
b
        Leaf3 MBR
_ a
a MBR
_ a
b MBR
_ a
c     ->       b -> a -> b
leaf (b -> a -> b
leaf (b -> a -> b
leaf b
z a
a) a
b) a
c
        Leaf4 MBR
_ a
a MBR
_ a
b MBR
_ a
c MBR
_ a
d -> b -> a -> b
leaf (b -> a -> b
leaf (b -> a -> b
leaf (b -> a -> b
leaf b
z a
a) a
b) a
c) a
d

        Leaf1 MBR
_ a
a             -> b -> a -> b
leaf b
z a
a
        R2Tree a
Empty                 -> b
z


-- | \(\mathcal{O}(n_R)\).
--   Fold left-to-right over all t'MBR's and their respective values.
foldlWithKey :: (b -> MBR -> a -> b) -> b -> R2Tree a -> b
foldlWithKey :: forall b a. (b -> MBR -> a -> b) -> b -> R2Tree a -> b
foldlWithKey b -> MBR -> a -> b
f = b -> R2Tree a -> b
go
  where
    go :: b -> R2Tree a -> b
go b
z R2Tree a
n =
      case R2Tree a
n of
        Node2 MBR
_  R2Tree a
a MBR
_  R2Tree a
b           ->         b -> R2Tree a -> b
go (b -> R2Tree a -> b
go b
z R2Tree a
a) R2Tree a
b
        Node3 MBR
_  R2Tree a
a MBR
_  R2Tree a
b MBR
_  R2Tree a
c      ->     b -> R2Tree a -> b
go (b -> R2Tree a -> b
go (b -> R2Tree a -> b
go b
z R2Tree a
a) R2Tree a
b) R2Tree a
c
        Node4 MBR
_  R2Tree a
a MBR
_  R2Tree a
b MBR
_  R2Tree a
c MBR
_  R2Tree a
d -> b -> R2Tree a -> b
go (b -> R2Tree a -> b
go (b -> R2Tree a -> b
go (b -> R2Tree a -> b
go b
z R2Tree a
a) R2Tree a
b) R2Tree a
c) R2Tree a
d

        Leaf2 MBR
ba a
a MBR
bb a
b           ->       b -> MBR -> a -> b
f (b -> MBR -> a -> b
f b
z MBR
ba a
a) MBR
bb a
b
        Leaf3 MBR
ba a
a MBR
bb a
b MBR
bc a
c      ->    b -> MBR -> a -> b
f (b -> MBR -> a -> b
f (b -> MBR -> a -> b
f b
z MBR
ba a
a) MBR
bb a
b) MBR
bc a
c
        Leaf4 MBR
ba a
a MBR
bb a
b MBR
bc a
c MBR
bd a
d -> b -> MBR -> a -> b
f (b -> MBR -> a -> b
f (b -> MBR -> a -> b
f (b -> MBR -> a -> b
f b
z MBR
ba a
a) MBR
bb a
b) MBR
bc a
c) MBR
bd a
d

        Leaf1 MBR
ba a
a                -> b -> MBR -> a -> b
f b
z MBR
ba a
a
        R2Tree a
Empty                     -> b
z

-- | \(\mathcal{O}(n)\).
--   Fold left-to-right over all t'MBR's and their respective values,
--   applying the operator function strictly.
foldlWithKey' :: (b -> MBR -> a -> b) -> b -> R2Tree a -> b
foldlWithKey' :: forall b a. (b -> MBR -> a -> b) -> b -> R2Tree a -> b
foldlWithKey' b -> MBR -> a -> b
f = b -> R2Tree a -> b
go
  where
    {-# INLINE leaf #-}
    leaf :: b -> MBR -> a -> b
leaf !b
z MBR
bx a
x = b -> MBR -> a -> b
f b
z MBR
bx a
x

    go :: b -> R2Tree a -> b
go b
z R2Tree a
n =
      case R2Tree a
n of
        Node2 MBR
_  R2Tree a
a MBR
_  R2Tree a
b           ->         b -> R2Tree a -> b
go (b -> R2Tree a -> b
go b
z R2Tree a
a) R2Tree a
b
        Node3 MBR
_  R2Tree a
a MBR
_  R2Tree a
b MBR
_  R2Tree a
c      ->     b -> R2Tree a -> b
go (b -> R2Tree a -> b
go (b -> R2Tree a -> b
go b
z R2Tree a
a) R2Tree a
b) R2Tree a
c
        Node4 MBR
_  R2Tree a
a MBR
_  R2Tree a
b MBR
_  R2Tree a
c MBR
_  R2Tree a
d -> b -> R2Tree a -> b
go (b -> R2Tree a -> b
go (b -> R2Tree a -> b
go (b -> R2Tree a -> b
go b
z R2Tree a
a) R2Tree a
b) R2Tree a
c) R2Tree a
d

        Leaf2 MBR
ba a
a MBR
bb a
b           ->             b -> MBR -> a -> b
leaf (b -> MBR -> a -> b
leaf b
z MBR
ba a
a) MBR
bb a
b
        Leaf3 MBR
ba a
a MBR
bb a
b MBR
bc a
c      ->       b -> MBR -> a -> b
leaf (b -> MBR -> a -> b
leaf (b -> MBR -> a -> b
leaf b
z MBR
ba a
a) MBR
bb a
b) MBR
bc a
c
        Leaf4 MBR
ba a
a MBR
bb a
b MBR
bc a
c MBR
bd a
d -> b -> MBR -> a -> b
leaf (b -> MBR -> a -> b
leaf (b -> MBR -> a -> b
leaf (b -> MBR -> a -> b
leaf b
z MBR
ba a
a) MBR
bb a
b) MBR
bc a
c) MBR
bd a
d
 
        Leaf1 MBR
ba a
a                -> b -> MBR -> a -> b
leaf b
z MBR
ba a
a
        R2Tree a
Empty                     -> b
z


{-# INLINE foldlRangeWithKey #-}
-- | \(\mathcal{O}(\log n + n_{I_R})\).
--   Fold left-to-right over t'MBR's that match the 'Predicate'
--   and their respective values.
foldlRangeWithKey :: Predicate -> (b -> MBR -> a -> b) -> b -> R2Tree a -> b
foldlRangeWithKey :: forall b a. Predicate -> (b -> MBR -> a -> b) -> b -> R2Tree a -> b
foldlRangeWithKey (Predicate MBR -> Bool
nodePred MBR -> Bool
leafPred) b -> MBR -> a -> b
f = b -> R2Tree a -> b
go
  where
    {-# INLINE node #-}
    node :: b -> MBR -> R2Tree a -> b
node b
z MBR
bx R2Tree a
x
      | MBR -> Bool
nodePred MBR
bx = b -> R2Tree a -> b
go b
z R2Tree a
x
      | Bool
otherwise   = b
z

    {-# INLINE leaf #-}
    leaf :: b -> MBR -> a -> b
leaf b
z MBR
bx a
x
      | MBR -> Bool
leafPred MBR
bx = b -> MBR -> a -> b
f b
z MBR
bx a
x
      | Bool
otherwise   = b
z

    go :: b -> R2Tree a -> b
go b
z R2Tree a
n =
      case R2Tree a
n of
        Node2 MBR
ba R2Tree a
a MBR
bb R2Tree a
b           ->             b -> MBR -> R2Tree a -> b
node (b -> MBR -> R2Tree a -> b
node b
z MBR
ba R2Tree a
a) MBR
bb R2Tree a
b
        Node3 MBR
ba R2Tree a
a MBR
bb R2Tree a
b MBR
bc R2Tree a
c      ->       b -> MBR -> R2Tree a -> b
node (b -> MBR -> R2Tree a -> b
node (b -> MBR -> R2Tree a -> b
node b
z MBR
ba R2Tree a
a) MBR
bb R2Tree a
b) MBR
bc R2Tree a
c
        Node4 MBR
ba R2Tree a
a MBR
bb R2Tree a
b MBR
bc R2Tree a
c MBR
bd R2Tree a
d -> b -> MBR -> R2Tree a -> b
node (b -> MBR -> R2Tree a -> b
node (b -> MBR -> R2Tree a -> b
node (b -> MBR -> R2Tree a -> b
node b
z MBR
ba R2Tree a
a) MBR
bb R2Tree a
b) MBR
bc R2Tree a
c) MBR
bd R2Tree a
d

        Leaf2 MBR
ba a
a MBR
bb a
b           ->             b -> MBR -> a -> b
leaf (b -> MBR -> a -> b
leaf b
z MBR
ba a
a) MBR
bb a
b
        Leaf3 MBR
ba a
a MBR
bb a
b MBR
bc a
c      ->       b -> MBR -> a -> b
leaf (b -> MBR -> a -> b
leaf (b -> MBR -> a -> b
leaf b
z MBR
ba a
a) MBR
bb a
b) MBR
bc a
c
        Leaf4 MBR
ba a
a MBR
bb a
b MBR
bc a
c MBR
bd a
d -> b -> MBR -> a -> b
leaf (b -> MBR -> a -> b
leaf (b -> MBR -> a -> b
leaf (b -> MBR -> a -> b
leaf b
z MBR
ba a
a) MBR
bb a
b) MBR
bc a
c) MBR
bd a
d

        Leaf1 MBR
ba a
a                -> b -> MBR -> a -> b
leaf b
z MBR
ba a
a
        R2Tree a
Empty                     -> b
z

{-# INLINE foldlRangeWithKey' #-}
-- | \(\mathcal{O}(\log n + n_I)\).
--   Fold left-to-right over t'MBR's that match the 'Predicate'
--   and their respective values, applying the operator function strictly.
foldlRangeWithKey' :: Predicate -> (b -> MBR -> a -> b) -> b -> R2Tree a -> b
foldlRangeWithKey' :: forall b a. Predicate -> (b -> MBR -> a -> b) -> b -> R2Tree a -> b
foldlRangeWithKey' (Predicate MBR -> Bool
nodePred MBR -> Bool
leafPred) b -> MBR -> a -> b
f = b -> R2Tree a -> b
go
  where
    {-# INLINE node #-}
    node :: b -> MBR -> R2Tree a -> b
node b
z MBR
bx R2Tree a
x
      | MBR -> Bool
nodePred MBR
bx = b -> R2Tree a -> b
go b
z R2Tree a
x
      | Bool
otherwise   = b
z

    {-# INLINE leaf #-}
    leaf :: b -> MBR -> a -> b
leaf !b
z MBR
bx a
x
      | MBR -> Bool
leafPred MBR
bx = b -> MBR -> a -> b
f b
z MBR
bx a
x
      | Bool
otherwise   = b
z

    go :: b -> R2Tree a -> b
go b
z R2Tree a
n =
      case R2Tree a
n of
        Node2 MBR
ba R2Tree a
a MBR
bb R2Tree a
b           ->             b -> MBR -> R2Tree a -> b
node (b -> MBR -> R2Tree a -> b
node b
z MBR
ba R2Tree a
a) MBR
bb R2Tree a
b
        Node3 MBR
ba R2Tree a
a MBR
bb R2Tree a
b MBR
bc R2Tree a
c      ->       b -> MBR -> R2Tree a -> b
node (b -> MBR -> R2Tree a -> b
node (b -> MBR -> R2Tree a -> b
node b
z MBR
ba R2Tree a
a) MBR
bb R2Tree a
b) MBR
bc R2Tree a
c
        Node4 MBR
ba R2Tree a
a MBR
bb R2Tree a
b MBR
bc R2Tree a
c MBR
bd R2Tree a
d -> b -> MBR -> R2Tree a -> b
node (b -> MBR -> R2Tree a -> b
node (b -> MBR -> R2Tree a -> b
node (b -> MBR -> R2Tree a -> b
node b
z MBR
ba R2Tree a
a) MBR
bb R2Tree a
b) MBR
bc R2Tree a
c) MBR
bd R2Tree a
d

        Leaf2 MBR
ba a
a MBR
bb a
b           ->             b -> MBR -> a -> b
leaf (b -> MBR -> a -> b
leaf b
z MBR
ba a
a) MBR
bb a
b
        Leaf3 MBR
ba a
a MBR
bb a
b MBR
bc a
c      ->       b -> MBR -> a -> b
leaf (b -> MBR -> a -> b
leaf (b -> MBR -> a -> b
leaf b
z MBR
ba a
a) MBR
bb a
b) MBR
bc a
c
        Leaf4 MBR
ba a
a MBR
bb a
b MBR
bc a
c MBR
bd a
d -> b -> MBR -> a -> b
leaf (b -> MBR -> a -> b
leaf (b -> MBR -> a -> b
leaf (b -> MBR -> a -> b
leaf b
z MBR
ba a
a) MBR
bb a
b) MBR
bc a
c) MBR
bd a
d

        Leaf1 MBR
ba a
a                -> b -> MBR -> a -> b
leaf b
z MBR
ba a
a
        R2Tree a
Empty                     -> b
z



-- | \(\mathcal{O}(n_L)\).
--   Fold right-to-left over all values.
foldr :: (a -> b -> b) -> b -> R2Tree a -> b
foldr :: forall a b. (a -> b -> b) -> b -> R2Tree a -> b
foldr a -> b -> b
f = b -> R2Tree a -> b
go
  where
    go :: b -> R2Tree a -> b
go b
z R2Tree a
n =
      case R2Tree a
n of
        Node2 MBR
_  R2Tree a
a MBR
_  R2Tree a
b           -> b -> R2Tree a -> b
go (b -> R2Tree a -> b
go         b
z       R2Tree a
b) R2Tree a
a
        Node3 MBR
_  R2Tree a
a MBR
_  R2Tree a
b MBR
_  R2Tree a
c      -> b -> R2Tree a -> b
go (b -> R2Tree a -> b
go (b -> R2Tree a -> b
go     b
z    R2Tree a
c) R2Tree a
b) R2Tree a
a
        Node4 MBR
_  R2Tree a
a MBR
_  R2Tree a
b MBR
_  R2Tree a
c MBR
_  R2Tree a
d -> b -> R2Tree a -> b
go (b -> R2Tree a -> b
go (b -> R2Tree a -> b
go (b -> R2Tree a -> b
go b
z R2Tree a
d) R2Tree a
c) R2Tree a
b) R2Tree a
a

        Leaf2 MBR
_  a
a MBR
_  a
b           -> a -> b -> b
f a
a (a -> b -> b
f a
b           b
z)
        Leaf3 MBR
_  a
a MBR
_  a
b MBR
_  a
c      -> a -> b -> b
f a
a (a -> b -> b
f a
b (a -> b -> b
f a
c      b
z))
        Leaf4 MBR
_  a
a MBR
_  a
b MBR
_  a
c MBR
_  a
d -> a -> b -> b
f a
a (a -> b -> b
f a
b (a -> b -> b
f a
c (a -> b -> b
f a
d b
z)))

        Leaf1 MBR
_ a
a                 -> a -> b -> b
f a
a b
z
        R2Tree a
Empty                     -> b
z

-- | \(\mathcal{O}(n)\).
--   Fold right-to-left over all values, applying the operator function strictly.
foldr' :: (a -> b -> b) -> b -> R2Tree a -> b
foldr' :: forall a b. (a -> b -> b) -> b -> R2Tree a -> b
foldr' a -> b -> b
f = b -> R2Tree a -> b
go
  where
    {-# INLINE leaf #-}
    leaf :: a -> b -> b
leaf a
x !b
z = a -> b -> b
f a
x b
z

    go :: b -> R2Tree a -> b
go b
z R2Tree a
n =
      case R2Tree a
n of
        Node2 MBR
_  R2Tree a
a MBR
_  R2Tree a
b           -> b -> R2Tree a -> b
go (b -> R2Tree a -> b
go         b
z       R2Tree a
b) R2Tree a
a
        Node3 MBR
_  R2Tree a
a MBR
_  R2Tree a
b MBR
_  R2Tree a
c      -> b -> R2Tree a -> b
go (b -> R2Tree a -> b
go (b -> R2Tree a -> b
go     b
z    R2Tree a
c) R2Tree a
b) R2Tree a
a
        Node4 MBR
_  R2Tree a
a MBR
_  R2Tree a
b MBR
_  R2Tree a
c MBR
_  R2Tree a
d -> b -> R2Tree a -> b
go (b -> R2Tree a -> b
go (b -> R2Tree a -> b
go (b -> R2Tree a -> b
go b
z R2Tree a
d) R2Tree a
c) R2Tree a
b) R2Tree a
a

        Leaf2 MBR
_  a
a MBR
_  a
b           -> a -> b -> b
leaf a
a (a -> b -> b
leaf a
b                 b
z)
        Leaf3 MBR
_  a
a MBR
_  a
b MBR
_  a
c      -> a -> b -> b
leaf a
a (a -> b -> b
leaf a
b (a -> b -> b
leaf a
c         b
z))
        Leaf4 MBR
_  a
a MBR
_  a
b MBR
_  a
c MBR
_  a
d -> a -> b -> b
leaf a
a (a -> b -> b
leaf a
b (a -> b -> b
leaf a
c (a -> b -> b
leaf a
d b
z)))

        Leaf1 MBR
_ a
a                 -> a -> b -> b
leaf a
a b
z
        R2Tree a
Empty                     -> b
z


-- | \(\mathcal{O}(n_L)\).
--   Fold right-to-left over all t'MBR's and their respective values.
foldrWithKey :: (MBR -> a -> b -> b) -> b -> R2Tree a -> b
foldrWithKey :: forall a b. (MBR -> a -> b -> b) -> b -> R2Tree a -> b
foldrWithKey MBR -> a -> b -> b
f = b -> R2Tree a -> b
go
  where
    go :: b -> R2Tree a -> b
go b
z R2Tree a
n =
      case R2Tree a
n of
        Node2 MBR
_  R2Tree a
a MBR
_  R2Tree a
b           -> b -> R2Tree a -> b
go (b -> R2Tree a -> b
go         b
z       R2Tree a
b) R2Tree a
a
        Node3 MBR
_  R2Tree a
a MBR
_  R2Tree a
b MBR
_  R2Tree a
c      -> b -> R2Tree a -> b
go (b -> R2Tree a -> b
go (b -> R2Tree a -> b
go     b
z    R2Tree a
c) R2Tree a
b) R2Tree a
a
        Node4 MBR
_  R2Tree a
a MBR
_  R2Tree a
b MBR
_  R2Tree a
c MBR
_  R2Tree a
d -> b -> R2Tree a -> b
go (b -> R2Tree a -> b
go (b -> R2Tree a -> b
go (b -> R2Tree a -> b
go b
z R2Tree a
d) R2Tree a
c) R2Tree a
b) R2Tree a
a

        Leaf2 MBR
ba a
a MBR
bb a
b           -> MBR -> a -> b -> b
f MBR
ba a
a (MBR -> a -> b -> b
f MBR
bb a
b                 b
z)
        Leaf3 MBR
ba a
a MBR
bb a
b MBR
bc a
c      -> MBR -> a -> b -> b
f MBR
ba a
a (MBR -> a -> b -> b
f MBR
bb a
b (MBR -> a -> b -> b
f MBR
bc a
c         b
z))
        Leaf4 MBR
ba a
a MBR
bb a
b MBR
bc a
c MBR
bd a
d -> MBR -> a -> b -> b
f MBR
ba a
a (MBR -> a -> b -> b
f MBR
bb a
b (MBR -> a -> b -> b
f MBR
bc a
c (MBR -> a -> b -> b
f MBR
bd a
d b
z)))

        Leaf1 MBR
ba a
a                -> MBR -> a -> b -> b
f MBR
ba a
a b
z
        R2Tree a
Empty                     -> b
z

-- | \(\mathcal{O}(n)\).
--   Fold right-to-left over all t'MBR's and their respective values,
--   applying the operator function strictly.
foldrWithKey' :: (MBR -> a -> b -> b) -> b -> R2Tree a -> b
foldrWithKey' :: forall a b. (MBR -> a -> b -> b) -> b -> R2Tree a -> b
foldrWithKey' MBR -> a -> b -> b
f = b -> R2Tree a -> b
go
  where
    {-# INLINE leaf #-}
    leaf :: MBR -> a -> b -> b
leaf MBR
bx a
x !b
z = MBR -> a -> b -> b
f MBR
bx a
x b
z

    go :: b -> R2Tree a -> b
go b
z R2Tree a
n =
      case R2Tree a
n of
        Node2 MBR
_  R2Tree a
a MBR
_  R2Tree a
b           -> b -> R2Tree a -> b
go (b -> R2Tree a -> b
go         b
z       R2Tree a
b) R2Tree a
a
        Node3 MBR
_  R2Tree a
a MBR
_  R2Tree a
b MBR
_  R2Tree a
c      -> b -> R2Tree a -> b
go (b -> R2Tree a -> b
go (b -> R2Tree a -> b
go     b
z    R2Tree a
c) R2Tree a
b) R2Tree a
a
        Node4 MBR
_  R2Tree a
a MBR
_  R2Tree a
b MBR
_  R2Tree a
c MBR
_  R2Tree a
d -> b -> R2Tree a -> b
go (b -> R2Tree a -> b
go (b -> R2Tree a -> b
go (b -> R2Tree a -> b
go b
z R2Tree a
d) R2Tree a
c) R2Tree a
b) R2Tree a
a

        Leaf2 MBR
ba a
a MBR
bb a
b           -> MBR -> a -> b -> b
leaf MBR
ba a
a (MBR -> a -> b -> b
leaf MBR
bb a
b                       b
z)
        Leaf3 MBR
ba a
a MBR
bb a
b MBR
bc a
c      -> MBR -> a -> b -> b
leaf MBR
ba a
a (MBR -> a -> b -> b
leaf MBR
bb a
b (MBR -> a -> b -> b
leaf MBR
bc a
c            b
z))
        Leaf4 MBR
ba a
a MBR
bb a
b MBR
bc a
c MBR
bd a
d -> MBR -> a -> b -> b
leaf MBR
ba a
a (MBR -> a -> b -> b
leaf MBR
bb a
b (MBR -> a -> b -> b
leaf MBR
bc a
c (MBR -> a -> b -> b
leaf MBR
bd a
d b
z)))

        Leaf1 MBR
ba a
a                -> MBR -> a -> b -> b
leaf MBR
ba a
a b
z
        R2Tree a
Empty                     -> b
z


{-# INLINE foldrRangeWithKey #-}
-- | \(\mathcal{O}(\log n + n_{I_L})\).
--   Fold right-to-left over t'MBR's that match the 'Predicate'
--   and their respective values.
foldrRangeWithKey :: Predicate -> (MBR -> a -> b -> b) -> b -> R2Tree a -> b
foldrRangeWithKey :: forall a b. Predicate -> (MBR -> a -> b -> b) -> b -> R2Tree a -> b
foldrRangeWithKey (Predicate MBR -> Bool
nodePred MBR -> Bool
leafPred) MBR -> a -> b -> b
f = b -> R2Tree a -> b
go
  where
    {-# INLINE node #-}
    node :: b -> MBR -> R2Tree a -> b
node b
z MBR
bx R2Tree a
x
      | MBR -> Bool
nodePred MBR
bx = b -> R2Tree a -> b
go b
z R2Tree a
x
      | Bool
otherwise   = b
z

    {-# INLINE leaf #-}
    leaf :: MBR -> a -> b -> b
leaf MBR
bx a
x b
z
      | MBR -> Bool
leafPred MBR
bx = MBR -> a -> b -> b
f MBR
bx a
x b
z
      | Bool
otherwise   = b
z

    go :: b -> R2Tree a -> b
go b
z R2Tree a
n =
      case R2Tree a
n of
        Node2 MBR
ba R2Tree a
a MBR
bb R2Tree a
b           -> b -> MBR -> R2Tree a -> b
node (b -> MBR -> R2Tree a -> b
node             b
z             MBR
bb R2Tree a
b) MBR
ba R2Tree a
a
        Node3 MBR
ba R2Tree a
a MBR
bb R2Tree a
b MBR
bc R2Tree a
c      -> b -> MBR -> R2Tree a -> b
node (b -> MBR -> R2Tree a -> b
node (b -> MBR -> R2Tree a -> b
node       b
z       MBR
bc R2Tree a
c) MBR
bb R2Tree a
b) MBR
ba R2Tree a
a
        Node4 MBR
ba R2Tree a
a MBR
bb R2Tree a
b MBR
bc R2Tree a
c MBR
bd R2Tree a
d -> b -> MBR -> R2Tree a -> b
node (b -> MBR -> R2Tree a -> b
node (b -> MBR -> R2Tree a -> b
node (b -> MBR -> R2Tree a -> b
node b
z MBR
bd R2Tree a
d) MBR
bc R2Tree a
c) MBR
bb R2Tree a
b) MBR
ba R2Tree a
a

        Leaf2 MBR
ba a
a MBR
bb a
b           -> MBR -> a -> b -> b
leaf MBR
ba a
a (MBR -> a -> b -> b
leaf MBR
bb a
b                       b
z)
        Leaf3 MBR
ba a
a MBR
bb a
b MBR
bc a
c      -> MBR -> a -> b -> b
leaf MBR
ba a
a (MBR -> a -> b -> b
leaf MBR
bb a
b (MBR -> a -> b -> b
leaf MBR
bc a
c            b
z))
        Leaf4 MBR
ba a
a MBR
bb a
b MBR
bc a
c MBR
bd a
d -> MBR -> a -> b -> b
leaf MBR
ba a
a (MBR -> a -> b -> b
leaf MBR
bb a
b (MBR -> a -> b -> b
leaf MBR
bc a
c (MBR -> a -> b -> b
leaf MBR
bd a
d b
z)))

        Leaf1 MBR
ba a
a -> MBR -> a -> b -> b
leaf MBR
ba a
a b
z
        R2Tree a
Empty      -> b
z

{-# INLINE foldrRangeWithKey' #-}
-- | \(\mathcal{O}(\log n + n_I)\).
--   Fold right-to-left over t'MBR's that match the 'Predicate'
--   and their respective values, applying the operator function strictly.
foldrRangeWithKey' :: Predicate -> (MBR -> a -> b -> b) -> b -> R2Tree a -> b
foldrRangeWithKey' :: forall a b. Predicate -> (MBR -> a -> b -> b) -> b -> R2Tree a -> b
foldrRangeWithKey' (Predicate MBR -> Bool
nodePred MBR -> Bool
leafPred) MBR -> a -> b -> b
f = b -> R2Tree a -> b
go
  where
    {-# INLINE node #-}
    node :: b -> MBR -> R2Tree a -> b
node b
z MBR
bx R2Tree a
x
      | MBR -> Bool
nodePred MBR
bx = b -> R2Tree a -> b
go b
z R2Tree a
x
      | Bool
otherwise   = b
z

    {-# INLINE leaf #-}
    leaf :: MBR -> a -> b -> b
leaf MBR
bx a
x !b
z
      | MBR -> Bool
leafPred MBR
bx = MBR -> a -> b -> b
f MBR
bx a
x b
z
      | Bool
otherwise   = b
z

    go :: b -> R2Tree a -> b
go b
z R2Tree a
n =
      case R2Tree a
n of
        Node2 MBR
ba R2Tree a
a MBR
bb R2Tree a
b           -> b -> MBR -> R2Tree a -> b
node (b -> MBR -> R2Tree a -> b
node             b
z             MBR
bb R2Tree a
b) MBR
ba R2Tree a
a
        Node3 MBR
ba R2Tree a
a MBR
bb R2Tree a
b MBR
bc R2Tree a
c      -> b -> MBR -> R2Tree a -> b
node (b -> MBR -> R2Tree a -> b
node (b -> MBR -> R2Tree a -> b
node       b
z       MBR
bc R2Tree a
c) MBR
bb R2Tree a
b) MBR
ba R2Tree a
a
        Node4 MBR
ba R2Tree a
a MBR
bb R2Tree a
b MBR
bc R2Tree a
c MBR
bd R2Tree a
d -> b -> MBR -> R2Tree a -> b
node (b -> MBR -> R2Tree a -> b
node (b -> MBR -> R2Tree a -> b
node (b -> MBR -> R2Tree a -> b
node b
z MBR
bd R2Tree a
d) MBR
bc R2Tree a
c) MBR
bb R2Tree a
b) MBR
ba R2Tree a
a

        Leaf2 MBR
ba a
a MBR
bb a
b           -> MBR -> a -> b -> b
leaf MBR
ba a
a (MBR -> a -> b -> b
leaf MBR
bb a
b                       b
z)
        Leaf3 MBR
ba a
a MBR
bb a
b MBR
bc a
c      -> MBR -> a -> b -> b
leaf MBR
ba a
a (MBR -> a -> b -> b
leaf MBR
bb a
b (MBR -> a -> b -> b
leaf MBR
bc a
c            b
z))
        Leaf4 MBR
ba a
a MBR
bb a
b MBR
bc a
c MBR
bd a
d -> MBR -> a -> b -> b
leaf MBR
ba a
a (MBR -> a -> b -> b
leaf MBR
bb a
b (MBR -> a -> b -> b
leaf MBR
bc a
c (MBR -> a -> b -> b
leaf MBR
bd a
d b
z)))

        Leaf1 MBR
ba a
a                -> MBR -> a -> b -> b
leaf MBR
ba a
a b
z
        R2Tree a
Empty                     -> b
z



-- | \(\mathcal{O}(n_M)\).
--   Map each value to a monoid and combine the results.
foldMap :: Monoid m => (a -> m) -> R2Tree a -> m
foldMap :: forall m a. Monoid m => (a -> m) -> R2Tree a -> m
foldMap a -> m
f = R2Tree a -> m
go
  where
    go :: R2Tree a -> m
go R2Tree a
n =
      case R2Tree a
n of
        Node2 MBR
_  R2Tree a
a MBR
_  R2Tree a
b           -> R2Tree a -> m
go R2Tree a
a m -> m -> m
forall a. Semigroup a => a -> a -> a
<> R2Tree a -> m
go R2Tree a
b
        Node3 MBR
_  R2Tree a
a MBR
_  R2Tree a
b MBR
_  R2Tree a
c      -> R2Tree a -> m
go R2Tree a
a m -> m -> m
forall a. Semigroup a => a -> a -> a
<> R2Tree a -> m
go R2Tree a
b m -> m -> m
forall a. Semigroup a => a -> a -> a
<> R2Tree a -> m
go R2Tree a
c
        Node4 MBR
_  R2Tree a
a MBR
_  R2Tree a
b MBR
_  R2Tree a
c MBR
_  R2Tree a
d -> R2Tree a -> m
go R2Tree a
a m -> m -> m
forall a. Semigroup a => a -> a -> a
<> R2Tree a -> m
go R2Tree a
b m -> m -> m
forall a. Semigroup a => a -> a -> a
<> R2Tree a -> m
go R2Tree a
c m -> m -> m
forall a. Semigroup a => a -> a -> a
<> R2Tree a -> m
go R2Tree a
d

        Leaf2 MBR
_  a
a MBR
_  a
b           -> a -> m
f a
a m -> m -> m
forall a. Semigroup a => a -> a -> a
<> a -> m
f a
b
        Leaf3 MBR
_  a
a MBR
_  a
b MBR
_  a
c      -> a -> m
f a
a m -> m -> m
forall a. Semigroup a => a -> a -> a
<> a -> m
f a
b m -> m -> m
forall a. Semigroup a => a -> a -> a
<> a -> m
f a
c
        Leaf4 MBR
_  a
a MBR
_  a
b MBR
_  a
c MBR
_  a
d -> a -> m
f a
a m -> m -> m
forall a. Semigroup a => a -> a -> a
<> a -> m
f a
b m -> m -> m
forall a. Semigroup a => a -> a -> a
<> a -> m
f a
c m -> m -> m
forall a. Semigroup a => a -> a -> a
<> a -> m
f a
d

        Leaf1 MBR
_ a
a                 -> a -> m
f a
a
        R2Tree a
Empty                     -> m
forall a. Monoid a => a
mempty


-- | \(\mathcal{O}(n_M)\).
--   Map each t'MBR' and its respective value to a monoid and combine the results.
foldMapWithKey :: Monoid m => (MBR -> a -> m) -> R2Tree a -> m
foldMapWithKey :: forall m a. Monoid m => (MBR -> a -> m) -> R2Tree a -> m
foldMapWithKey MBR -> a -> m
f = R2Tree a -> m
go
  where
    go :: R2Tree a -> m
go R2Tree a
n =
      case R2Tree a
n of
        Node2 MBR
_  R2Tree a
a MBR
_  R2Tree a
b           -> R2Tree a -> m
go R2Tree a
a m -> m -> m
forall a. Semigroup a => a -> a -> a
<> R2Tree a -> m
go R2Tree a
b
        Node3 MBR
_  R2Tree a
a MBR
_  R2Tree a
b MBR
_  R2Tree a
c      -> R2Tree a -> m
go R2Tree a
a m -> m -> m
forall a. Semigroup a => a -> a -> a
<> R2Tree a -> m
go R2Tree a
b m -> m -> m
forall a. Semigroup a => a -> a -> a
<> R2Tree a -> m
go R2Tree a
c
        Node4 MBR
_  R2Tree a
a MBR
_  R2Tree a
b MBR
_  R2Tree a
c MBR
_  R2Tree a
d -> R2Tree a -> m
go R2Tree a
a m -> m -> m
forall a. Semigroup a => a -> a -> a
<> R2Tree a -> m
go R2Tree a
b m -> m -> m
forall a. Semigroup a => a -> a -> a
<> R2Tree a -> m
go R2Tree a
c m -> m -> m
forall a. Semigroup a => a -> a -> a
<> R2Tree a -> m
go R2Tree a
d

        Leaf2 MBR
ba a
a MBR
bb a
b           -> MBR -> a -> m
f MBR
ba a
a m -> m -> m
forall a. Semigroup a => a -> a -> a
<> MBR -> a -> m
f MBR
bb a
b
        Leaf3 MBR
ba a
a MBR
bb a
b MBR
bc a
c      -> MBR -> a -> m
f MBR
ba a
a m -> m -> m
forall a. Semigroup a => a -> a -> a
<> MBR -> a -> m
f MBR
bb a
b m -> m -> m
forall a. Semigroup a => a -> a -> a
<> MBR -> a -> m
f MBR
bc a
c
        Leaf4 MBR
ba a
a MBR
bb a
b MBR
bc a
c MBR
bd a
d -> MBR -> a -> m
f MBR
ba a
a m -> m -> m
forall a. Semigroup a => a -> a -> a
<> MBR -> a -> m
f MBR
bb a
b m -> m -> m
forall a. Semigroup a => a -> a -> a
<> MBR -> a -> m
f MBR
bc a
c m -> m -> m
forall a. Semigroup a => a -> a -> a
<> MBR -> a -> m
f MBR
bd a
d

        Leaf1 MBR
ba a
a                -> MBR -> a -> m
f MBR
ba a
a
        R2Tree a
Empty                     -> m
forall a. Monoid a => a
mempty


{-# INLINE foldMapRangeWithKey #-}
-- | \(\mathcal{O}(\log n + n_{I_M})\).
--   Map each t'MBR' that matches the 'Predicate' and its respective value to a monoid
--   and combine the results.
foldMapRangeWithKey :: Monoid m => Predicate -> (MBR -> a -> m) -> R2Tree a -> m
foldMapRangeWithKey :: forall m a.
Monoid m =>
Predicate -> (MBR -> a -> m) -> R2Tree a -> m
foldMapRangeWithKey (Predicate MBR -> Bool
nodePred MBR -> Bool
leafPred) MBR -> a -> m
f = R2Tree a -> m
go
  where
    {-# INLINE node #-}
    node :: MBR -> R2Tree a -> m
node MBR
bx R2Tree a
x
      | MBR -> Bool
nodePred MBR
bx = R2Tree a -> m
go R2Tree a
x
      | Bool
otherwise   = m
forall a. Monoid a => a
mempty

    {-# INLINE leaf #-}
    leaf :: MBR -> a -> m
leaf MBR
bx a
x
      | MBR -> Bool
leafPred MBR
bx = MBR -> a -> m
f MBR
bx a
x
      | Bool
otherwise   = m
forall a. Monoid a => a
mempty

    go :: R2Tree a -> m
go R2Tree a
n =
      case R2Tree a
n of
        Node2 MBR
ba R2Tree a
a MBR
bb R2Tree a
b           -> MBR -> R2Tree a -> m
node MBR
ba R2Tree a
a m -> m -> m
forall a. Semigroup a => a -> a -> a
<> MBR -> R2Tree a -> m
node MBR
bb R2Tree a
b
        Node3 MBR
ba R2Tree a
a MBR
bb R2Tree a
b MBR
bc R2Tree a
c      -> MBR -> R2Tree a -> m
node MBR
ba R2Tree a
a m -> m -> m
forall a. Semigroup a => a -> a -> a
<> MBR -> R2Tree a -> m
node MBR
bb R2Tree a
b m -> m -> m
forall a. Semigroup a => a -> a -> a
<> MBR -> R2Tree a -> m
node MBR
bc R2Tree a
c
        Node4 MBR
ba R2Tree a
a MBR
bb R2Tree a
b MBR
bc R2Tree a
c MBR
bd R2Tree a
d -> MBR -> R2Tree a -> m
node MBR
ba R2Tree a
a m -> m -> m
forall a. Semigroup a => a -> a -> a
<> MBR -> R2Tree a -> m
node MBR
bb R2Tree a
b m -> m -> m
forall a. Semigroup a => a -> a -> a
<> MBR -> R2Tree a -> m
node MBR
bc R2Tree a
c m -> m -> m
forall a. Semigroup a => a -> a -> a
<> MBR -> R2Tree a -> m
node MBR
bd R2Tree a
d

        Leaf2 MBR
ba a
a MBR
bb a
b           -> MBR -> a -> m
leaf MBR
ba a
a m -> m -> m
forall a. Semigroup a => a -> a -> a
<> MBR -> a -> m
leaf MBR
bb a
b
        Leaf3 MBR
ba a
a MBR
bb a
b MBR
bc a
c      -> MBR -> a -> m
leaf MBR
ba a
a m -> m -> m
forall a. Semigroup a => a -> a -> a
<> MBR -> a -> m
leaf MBR
bb a
b m -> m -> m
forall a. Semigroup a => a -> a -> a
<> MBR -> a -> m
leaf MBR
bc a
c
        Leaf4 MBR
ba a
a MBR
bb a
b MBR
bc a
c MBR
bd a
d -> MBR -> a -> m
leaf MBR
ba a
a m -> m -> m
forall a. Semigroup a => a -> a -> a
<> MBR -> a -> m
leaf MBR
bb a
b m -> m -> m
forall a. Semigroup a => a -> a -> a
<> MBR -> a -> m
leaf MBR
bc a
c m -> m -> m
forall a. Semigroup a => a -> a -> a
<> MBR -> a -> m
leaf MBR
bd a
d

        Leaf1 MBR
ba a
a                -> MBR -> a -> m
leaf MBR
ba a
a
        R2Tree a
Empty                     -> m
forall a. Monoid a => a
mempty



-- | \(\mathcal{O}(n)\).
--   Map each value to an action, evaluate the actions left-to-right and
--   collect the results.
traverse :: Applicative f => (a -> f b) -> R2Tree a -> f (R2Tree b)
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> R2Tree a -> f (R2Tree b)
traverse a -> f b
f = R2Tree a -> f (R2Tree b)
go
  where
    go :: R2Tree a -> f (R2Tree b)
go R2Tree a
n =
      case R2Tree a
n of
        Node2 MBR
ba R2Tree a
a MBR
bb R2Tree a
b           ->
          (R2Tree b -> R2Tree b -> R2Tree b)
-> f (R2Tree b) -> f (R2Tree b) -> f (R2Tree b)
forall a b c. (a -> b -> c) -> f a -> f b -> f c
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 (\R2Tree b
a' R2Tree b
b' -> MBR -> R2Tree b -> MBR -> R2Tree b -> R2Tree b
forall a. MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node2 MBR
ba R2Tree b
a' MBR
bb R2Tree b
b')
            (R2Tree a -> f (R2Tree b)
go R2Tree a
a) (R2Tree a -> f (R2Tree b)
go R2Tree a
b)

        Node3 MBR
ba R2Tree a
a MBR
bb R2Tree a
b MBR
bc R2Tree a
c      ->
          (R2Tree b -> R2Tree b -> R2Tree b -> R2Tree b)
-> f (R2Tree b) -> f (R2Tree b) -> f (R2Tree b -> R2Tree b)
forall a b c. (a -> b -> c) -> f a -> f b -> f c
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 (\R2Tree b
a' R2Tree b
b' R2Tree b
c' -> MBR -> R2Tree b -> MBR -> R2Tree b -> MBR -> R2Tree b -> R2Tree b
forall a.
MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node3 MBR
ba R2Tree b
a' MBR
bb R2Tree b
b' MBR
bc R2Tree b
c')
            (R2Tree a -> f (R2Tree b)
go R2Tree a
a) (R2Tree a -> f (R2Tree b)
go R2Tree a
b) f (R2Tree b -> R2Tree b) -> f (R2Tree b) -> f (R2Tree b)
forall a b. f (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> R2Tree a -> f (R2Tree b)
go R2Tree a
c

        Node4 MBR
ba R2Tree a
a MBR
bb R2Tree a
b MBR
bc R2Tree a
c MBR
bd R2Tree a
d ->
          (R2Tree b -> R2Tree b -> R2Tree b -> R2Tree b -> R2Tree b)
-> f (R2Tree b)
-> f (R2Tree b)
-> f (R2Tree b -> R2Tree b -> R2Tree b)
forall a b c. (a -> b -> c) -> f a -> f b -> f c
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 (\R2Tree b
a' R2Tree b
b' R2Tree b
c' R2Tree b
d' -> MBR
-> R2Tree b
-> MBR
-> R2Tree b
-> MBR
-> R2Tree b
-> MBR
-> R2Tree b
-> R2Tree b
forall a.
MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> R2Tree a
Node4 MBR
ba R2Tree b
a' MBR
bb R2Tree b
b' MBR
bc R2Tree b
c' MBR
bd R2Tree b
d')
            (R2Tree a -> f (R2Tree b)
go R2Tree a
a) (R2Tree a -> f (R2Tree b)
go R2Tree a
b) f (R2Tree b -> R2Tree b -> R2Tree b)
-> f (R2Tree b) -> f (R2Tree b -> R2Tree b)
forall a b. f (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> R2Tree a -> f (R2Tree b)
go R2Tree a
c f (R2Tree b -> R2Tree b) -> f (R2Tree b) -> f (R2Tree b)
forall a b. f (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> R2Tree a -> f (R2Tree b)
go R2Tree a
d

        Leaf2 MBR
ba a
a MBR
bb a
b           ->
          (b -> b -> R2Tree b) -> f b -> f b -> f (R2Tree b)
forall a b c. (a -> b -> c) -> f a -> f b -> f c
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 (\b
a' b
b' -> MBR -> b -> MBR -> b -> R2Tree b
forall a. MBR -> a -> MBR -> a -> R2Tree a
Leaf2 MBR
ba b
a' MBR
bb b
b')
            (a -> f b
f a
a) (a -> f b
f a
b)

        Leaf3 MBR
ba a
a MBR
bb a
b MBR
bc a
c      ->
          (b -> b -> b -> R2Tree b) -> f b -> f b -> f (b -> R2Tree b)
forall a b c. (a -> b -> c) -> f a -> f b -> f c
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 (\b
a' b
b' b
c' -> MBR -> b -> MBR -> b -> MBR -> b -> R2Tree b
forall a. MBR -> a -> MBR -> a -> MBR -> a -> R2Tree a
Leaf3 MBR
ba b
a' MBR
bb b
b' MBR
bc b
c')
            (a -> f b
f a
a) (a -> f b
f a
b) f (b -> R2Tree b) -> f b -> f (R2Tree b)
forall a b. f (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> a -> f b
f a
c

        Leaf4 MBR
ba a
a MBR
bb a
b MBR
bc a
c MBR
bd a
d ->
          (b -> b -> b -> b -> R2Tree b)
-> f b -> f b -> f (b -> b -> R2Tree b)
forall a b c. (a -> b -> c) -> f a -> f b -> f c
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 (\b
a' b
b' b
c' b
d' -> MBR -> b -> MBR -> b -> MBR -> b -> MBR -> b -> R2Tree b
forall a. MBR -> a -> MBR -> a -> MBR -> a -> MBR -> a -> R2Tree a
Leaf4 MBR
ba b
a' MBR
bb b
b' MBR
bc b
c' MBR
bd b
d')
            (a -> f b
f a
a) (a -> f b
f a
b) f (b -> b -> R2Tree b) -> f b -> f (b -> R2Tree b)
forall a b. f (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> a -> f b
f a
c f (b -> R2Tree b) -> f b -> f (R2Tree b)
forall a b. f (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> a -> f b
f a
d

        Leaf1 MBR
ba a
a                ->
          MBR -> b -> R2Tree b
forall a. MBR -> a -> R2Tree a
Leaf1 MBR
ba (b -> R2Tree b) -> f b -> f (R2Tree b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f b
f a
a

        R2Tree a
Empty                     -> R2Tree b -> f (R2Tree b)
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure R2Tree b
forall a. R2Tree a
Empty


-- | \(\mathcal{O}(n)\).
--   Map each t'MBR' and its respective 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)
traverseWithKey :: forall (f :: * -> *) a b.
Applicative f =>
(MBR -> a -> f b) -> R2Tree a -> f (R2Tree b)
traverseWithKey MBR -> a -> f b
f = R2Tree a -> f (R2Tree b)
go
  where
    go :: R2Tree a -> f (R2Tree b)
go R2Tree a
n =
      case R2Tree a
n of
        Node2 MBR
ba R2Tree a
a MBR
bb R2Tree a
b           ->
          (R2Tree b -> R2Tree b -> R2Tree b)
-> f (R2Tree b) -> f (R2Tree b) -> f (R2Tree b)
forall a b c. (a -> b -> c) -> f a -> f b -> f c
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 (\R2Tree b
a' R2Tree b
b' -> MBR -> R2Tree b -> MBR -> R2Tree b -> R2Tree b
forall a. MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node2 MBR
ba R2Tree b
a' MBR
bb R2Tree b
b')
            (R2Tree a -> f (R2Tree b)
go R2Tree a
a) (R2Tree a -> f (R2Tree b)
go R2Tree a
b)

        Node3 MBR
ba R2Tree a
a MBR
bb R2Tree a
b MBR
bc R2Tree a
c      ->
          (R2Tree b -> R2Tree b -> R2Tree b -> R2Tree b)
-> f (R2Tree b) -> f (R2Tree b) -> f (R2Tree b -> R2Tree b)
forall a b c. (a -> b -> c) -> f a -> f b -> f c
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 (\R2Tree b
a' R2Tree b
b' R2Tree b
c' -> MBR -> R2Tree b -> MBR -> R2Tree b -> MBR -> R2Tree b -> R2Tree b
forall a.
MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node3 MBR
ba R2Tree b
a' MBR
bb R2Tree b
b' MBR
bc R2Tree b
c')
            (R2Tree a -> f (R2Tree b)
go R2Tree a
a) (R2Tree a -> f (R2Tree b)
go R2Tree a
b) f (R2Tree b -> R2Tree b) -> f (R2Tree b) -> f (R2Tree b)
forall a b. f (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> R2Tree a -> f (R2Tree b)
go R2Tree a
c

        Node4 MBR
ba R2Tree a
a MBR
bb R2Tree a
b MBR
bc R2Tree a
c MBR
bd R2Tree a
d ->
          (R2Tree b -> R2Tree b -> R2Tree b -> R2Tree b -> R2Tree b)
-> f (R2Tree b)
-> f (R2Tree b)
-> f (R2Tree b -> R2Tree b -> R2Tree b)
forall a b c. (a -> b -> c) -> f a -> f b -> f c
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 (\R2Tree b
a' R2Tree b
b' R2Tree b
c' R2Tree b
d' -> MBR
-> R2Tree b
-> MBR
-> R2Tree b
-> MBR
-> R2Tree b
-> MBR
-> R2Tree b
-> R2Tree b
forall a.
MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> R2Tree a
Node4 MBR
ba R2Tree b
a' MBR
bb R2Tree b
b' MBR
bc R2Tree b
c' MBR
bd R2Tree b
d')
            (R2Tree a -> f (R2Tree b)
go R2Tree a
a) (R2Tree a -> f (R2Tree b)
go R2Tree a
b) f (R2Tree b -> R2Tree b -> R2Tree b)
-> f (R2Tree b) -> f (R2Tree b -> R2Tree b)
forall a b. f (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> R2Tree a -> f (R2Tree b)
go R2Tree a
c f (R2Tree b -> R2Tree b) -> f (R2Tree b) -> f (R2Tree b)
forall a b. f (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> R2Tree a -> f (R2Tree b)
go R2Tree a
d

        Leaf2 MBR
ba a
a MBR
bb a
b           ->
          (b -> b -> R2Tree b) -> f b -> f b -> f (R2Tree b)
forall a b c. (a -> b -> c) -> f a -> f b -> f c
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 (\b
a' b
b' -> MBR -> b -> MBR -> b -> R2Tree b
forall a. MBR -> a -> MBR -> a -> R2Tree a
Leaf2 MBR
ba b
a' MBR
bb b
b')
            (MBR -> a -> f b
f MBR
ba a
a) (MBR -> a -> f b
f MBR
bb a
b)

        Leaf3 MBR
ba a
a MBR
bb a
b MBR
bc a
c      ->
          (b -> b -> b -> R2Tree b) -> f b -> f b -> f (b -> R2Tree b)
forall a b c. (a -> b -> c) -> f a -> f b -> f c
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 (\b
a' b
b' b
c' -> MBR -> b -> MBR -> b -> MBR -> b -> R2Tree b
forall a. MBR -> a -> MBR -> a -> MBR -> a -> R2Tree a
Leaf3 MBR
ba b
a' MBR
bb b
b' MBR
bc b
c')
            (MBR -> a -> f b
f MBR
ba a
a) (MBR -> a -> f b
f MBR
bb a
b) f (b -> R2Tree b) -> f b -> f (R2Tree b)
forall a b. f (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> MBR -> a -> f b
f MBR
bc a
c

        Leaf4 MBR
ba a
a MBR
bb a
b MBR
bc a
c MBR
bd a
d ->
          (b -> b -> b -> b -> R2Tree b)
-> f b -> f b -> f (b -> b -> R2Tree b)
forall a b c. (a -> b -> c) -> f a -> f b -> f c
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 (\b
a' b
b' b
c' b
d' -> MBR -> b -> MBR -> b -> MBR -> b -> MBR -> b -> R2Tree b
forall a. MBR -> a -> MBR -> a -> MBR -> a -> MBR -> a -> R2Tree a
Leaf4 MBR
ba b
a' MBR
bb b
b' MBR
bc b
c' MBR
bd b
d')
            (MBR -> a -> f b
f MBR
ba a
a) (MBR -> a -> f b
f MBR
bb a
b) f (b -> b -> R2Tree b) -> f b -> f (b -> R2Tree b)
forall a b. f (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> MBR -> a -> f b
f MBR
bc a
c f (b -> R2Tree b) -> f b -> f (R2Tree b)
forall a b. f (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> MBR -> a -> f b
f MBR
bd a
d

        Leaf1 MBR
ba a
a                ->
          MBR -> b -> R2Tree b
forall a. MBR -> a -> R2Tree a
Leaf1 MBR
ba (b -> R2Tree b) -> f b -> f (R2Tree b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MBR -> a -> f b
f MBR
ba a
a

        R2Tree a
Empty                     -> R2Tree b -> f (R2Tree b)
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure R2Tree b
forall a. R2Tree a
Empty


{-# INLINE traverseRangeWithKey #-}
-- | \(\mathcal{O}(\log n + n_I)\).
--   Map each t'MBR' that matches the 'Predicate' and its respective value to an action,
--   evaluate the actions left-to-right and collect the results.
traverseRangeWithKey
  :: Applicative f => Predicate -> (MBR -> a -> f a) -> R2Tree a -> f (R2Tree a)
traverseRangeWithKey :: forall (f :: * -> *) a.
Applicative f =>
Predicate -> (MBR -> a -> f a) -> R2Tree a -> f (R2Tree a)
traverseRangeWithKey (Predicate MBR -> Bool
nodePred MBR -> Bool
leafPred) MBR -> a -> f a
f = R2Tree a -> f (R2Tree a)
go
  where
    {-# INLINE node #-}
    node :: MBR -> R2Tree a -> f (R2Tree a)
node MBR
bx R2Tree a
x
      | MBR -> Bool
nodePred MBR
bx = R2Tree a -> f (R2Tree a)
go R2Tree a
x
      | Bool
otherwise   = R2Tree a -> f (R2Tree a)
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure R2Tree a
x

    {-# INLINE leaf #-}
    leaf :: MBR -> a -> f a
leaf MBR
bx a
x
      | MBR -> Bool
leafPred MBR
bx = MBR -> a -> f a
f MBR
bx a
x
      | Bool
otherwise   = a -> f a
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure a
x

    go :: R2Tree a -> f (R2Tree a)
go R2Tree a
n =
      case R2Tree a
n of
        Node2 MBR
ba R2Tree a
a MBR
bb R2Tree a
b           ->
          (R2Tree a -> R2Tree a -> R2Tree a)
-> f (R2Tree a) -> f (R2Tree a) -> f (R2Tree a)
forall a b c. (a -> b -> c) -> f a -> f b -> f c
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 (\R2Tree a
a' R2Tree a
b' -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
forall a. MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node2 MBR
ba R2Tree a
a' MBR
bb R2Tree a
b')
            (MBR -> R2Tree a -> f (R2Tree a)
node MBR
ba R2Tree a
a) (MBR -> R2Tree a -> f (R2Tree a)
node MBR
bb R2Tree a
b)

        Node3 MBR
ba R2Tree a
a MBR
bb R2Tree a
b MBR
bc R2Tree a
c      ->
          (R2Tree a -> R2Tree a -> R2Tree a -> R2Tree a)
-> f (R2Tree a) -> f (R2Tree a) -> f (R2Tree a -> R2Tree a)
forall a b c. (a -> b -> c) -> f a -> f b -> f c
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 (\R2Tree a
a' R2Tree a
b' R2Tree a
c' -> MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
forall a.
MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node3 MBR
ba R2Tree a
a' MBR
bb R2Tree a
b' MBR
bc R2Tree a
c')
            (MBR -> R2Tree a -> f (R2Tree a)
node MBR
ba R2Tree a
a) (MBR -> R2Tree a -> f (R2Tree a)
node MBR
bb R2Tree a
b) f (R2Tree a -> R2Tree a) -> f (R2Tree a) -> f (R2Tree a)
forall a b. f (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> MBR -> R2Tree a -> f (R2Tree a)
node MBR
bc R2Tree a
c

        Node4 MBR
ba R2Tree a
a MBR
bb R2Tree a
b MBR
bc R2Tree a
c MBR
bd R2Tree a
d ->
          (R2Tree a -> R2Tree a -> R2Tree a -> R2Tree a -> R2Tree a)
-> f (R2Tree a)
-> f (R2Tree a)
-> f (R2Tree a -> R2Tree a -> R2Tree a)
forall a b c. (a -> b -> c) -> f a -> f b -> f c
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 (\R2Tree a
a' R2Tree a
b' R2Tree a
c' R2Tree a
d' -> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> R2Tree a
forall a.
MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> R2Tree a
Node4 MBR
ba R2Tree a
a' MBR
bb R2Tree a
b' MBR
bc R2Tree a
c' MBR
bd R2Tree a
d')
            (MBR -> R2Tree a -> f (R2Tree a)
node MBR
ba R2Tree a
a) (MBR -> R2Tree a -> f (R2Tree a)
node MBR
bb R2Tree a
b) f (R2Tree a -> R2Tree a -> R2Tree a)
-> f (R2Tree a) -> f (R2Tree a -> R2Tree a)
forall a b. f (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> MBR -> R2Tree a -> f (R2Tree a)
node MBR
bc R2Tree a
c f (R2Tree a -> R2Tree a) -> f (R2Tree a) -> f (R2Tree a)
forall a b. f (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> MBR -> R2Tree a -> f (R2Tree a)
node MBR
bd R2Tree a
d

        Leaf2 MBR
ba a
a MBR
bb a
b           ->
          (a -> a -> R2Tree a) -> f a -> f a -> f (R2Tree a)
forall a b c. (a -> b -> c) -> f a -> f b -> f c
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 (\a
a' a
b' -> MBR -> a -> MBR -> a -> R2Tree a
forall a. MBR -> a -> MBR -> a -> R2Tree a
Leaf2 MBR
ba a
a' MBR
bb a
b')
            (MBR -> a -> f a
leaf MBR
ba a
a) (MBR -> a -> f a
leaf MBR
bb a
b)

        Leaf3 MBR
ba a
a MBR
bb a
b MBR
bc a
c      ->
          (a -> a -> a -> R2Tree a) -> f a -> f a -> f (a -> R2Tree a)
forall a b c. (a -> b -> c) -> f a -> f b -> f c
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 (\a
a' a
b' a
c' -> MBR -> a -> MBR -> a -> MBR -> a -> R2Tree a
forall a. MBR -> a -> MBR -> a -> MBR -> a -> R2Tree a
Leaf3 MBR
ba a
a' MBR
bb a
b' MBR
bc a
c')
            (MBR -> a -> f a
leaf MBR
ba a
a) (MBR -> a -> f a
leaf MBR
bb a
b) f (a -> R2Tree a) -> f a -> f (R2Tree a)
forall a b. f (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> MBR -> a -> f a
leaf MBR
bc a
c

        Leaf4 MBR
ba a
a MBR
bb a
b MBR
bc a
c MBR
bd a
d ->
          (a -> a -> a -> a -> R2Tree a)
-> f a -> f a -> f (a -> a -> R2Tree a)
forall a b c. (a -> b -> c) -> f a -> f b -> f c
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 (\a
a' a
b' a
c' a
d' -> MBR -> a -> MBR -> a -> MBR -> a -> MBR -> a -> R2Tree a
forall a. MBR -> a -> MBR -> a -> MBR -> a -> MBR -> a -> R2Tree a
Leaf4 MBR
ba a
a' MBR
bb a
b' MBR
bc a
c' MBR
bd a
d')
            (MBR -> a -> f a
leaf MBR
ba a
a) (MBR -> a -> f a
leaf MBR
bb a
b) f (a -> a -> R2Tree a) -> f a -> f (a -> R2Tree a)
forall a b. f (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> MBR -> a -> f a
leaf MBR
bc a
c f (a -> R2Tree a) -> f a -> f (R2Tree a)
forall a b. f (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> MBR -> a -> f a
leaf MBR
bd a
d

        Leaf1 MBR
ba a
a                ->
          MBR -> a -> R2Tree a
forall a. MBR -> a -> R2Tree a
Leaf1 MBR
ba (a -> R2Tree a) -> f a -> f (R2Tree a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MBR -> a -> f a
leaf MBR
ba a
a

        R2Tree a
Empty                     -> R2Tree a -> f (R2Tree a)
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure R2Tree a
forall a. R2Tree a
Empty



{-# INLINE union3MBR #-}
union3MBR :: MBR -> MBR -> MBR -> MBR
union3MBR :: MBR -> MBR -> MBR -> MBR
union3MBR MBR
ba MBR
bb MBR
bc = MBR -> MBR -> MBR
unionMBR (MBR -> MBR -> MBR
unionMBR MBR
ba MBR
bb) MBR
bc

{-# INLINE union4MBR #-}
union4MBR :: MBR -> MBR -> MBR -> MBR -> MBR
union4MBR :: MBR -> MBR -> MBR -> MBR -> MBR
union4MBR MBR
ba MBR
bb MBR
bc MBR
bd = MBR -> MBR -> MBR
unionMBR (MBR -> MBR -> MBR
unionMBR MBR
ba MBR
bb) (MBR -> MBR -> MBR
unionMBR MBR
bc MBR
bd)



data Gut a = GutOne MBR (R2Tree a)
           | GutTwo MBR (R2Tree a) MBR (R2Tree a)

-- | \(\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](https://en.wikipedia.org/w/index.php?title=R*-tree&oldid=1171720351#Performance)
--   for a graphic example).
insertGut :: MBR -> a -> R2Tree a -> R2Tree a
insertGut :: forall a. MBR -> a -> R2Tree a -> R2Tree a
insertGut MBR
bx a
x R2Tree a
t =
  case MBR -> a -> R2Tree a -> Gut a
forall a. MBR -> a -> R2Tree a -> Gut a
insertGutRoot MBR
bx a
x R2Tree a
t of
    GutOne MBR
_ R2Tree a
o       -> R2Tree a
o
    GutTwo MBR
bl R2Tree a
l MBR
br R2Tree a
r -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
forall a. MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node2 MBR
bl R2Tree a
l MBR
br R2Tree a
r


insertGutRoot :: MBR -> a -> R2Tree a -> Gut a
insertGutRoot :: forall a. MBR -> a -> R2Tree a -> Gut a
insertGutRoot MBR
bx a
x R2Tree a
n =
  case R2Tree a
n of
    Node2 MBR
ba R2Tree a
a MBR
bb R2Tree a
b           ->
      let !(# MBR
be, R2Tree a
e, !MBR
bz, !R2Tree a
z #) = MBR
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> (# MBR, R2Tree a, MBR, R2Tree a #)
forall a. MBR -> MBR -> a -> MBR -> a -> (# MBR, a, MBR, a #)
leastEnlargement2 MBR
bx MBR
ba R2Tree a
a MBR
bb R2Tree a
b
      in case MBR -> a -> MBR -> R2Tree a -> Gut a
forall a. MBR -> a -> MBR -> R2Tree a -> Gut a
insertGut_ MBR
bx a
x MBR
be R2Tree a
e of
           GutOne MBR
bo R2Tree a
o ->
             MBR -> R2Tree a -> Gut a
forall a. MBR -> R2Tree a -> Gut a
GutOne (MBR -> MBR -> MBR
unionMBR MBR
bo MBR
bz) (MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
forall a. MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node2 MBR
bo R2Tree a
o MBR
bz R2Tree a
z)

           GutTwo MBR
bl R2Tree a
l MBR
br R2Tree a
r ->
             MBR -> R2Tree a -> Gut a
forall a. MBR -> R2Tree a -> Gut a
GutOne (MBR -> MBR -> MBR -> MBR
union3MBR MBR
bl MBR
br MBR
bz) (MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
forall a.
MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node3 MBR
bl R2Tree a
l MBR
br R2Tree a
r MBR
bz R2Tree a
z)

    Node3 MBR
ba R2Tree a
a MBR
bb R2Tree a
b MBR
bc R2Tree a
c      ->
      let !(# MBR
be, R2Tree a
e, !MBR
by, !R2Tree a
y, !MBR
bz, !R2Tree a
z #) = MBR
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> (# MBR, R2Tree a, MBR, R2Tree a, MBR, R2Tree a #)
forall a.
MBR
-> MBR -> a -> MBR -> a -> MBR -> a -> (# MBR, a, MBR, a, MBR, a #)
leastEnlargement3 MBR
bx MBR
ba R2Tree a
a MBR
bb R2Tree a
b MBR
bc R2Tree a
c
      in case MBR -> a -> MBR -> R2Tree a -> Gut a
forall a. MBR -> a -> MBR -> R2Tree a -> Gut a
insertGut_ MBR
bx a
x MBR
be R2Tree a
e of
           GutOne MBR
bo R2Tree a
o ->
             MBR -> R2Tree a -> Gut a
forall a. MBR -> R2Tree a -> Gut a
GutOne (MBR -> MBR -> MBR -> MBR
union3MBR MBR
bo MBR
by MBR
bz) (MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
forall a.
MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node3 MBR
bo R2Tree a
o MBR
by R2Tree a
y MBR
bz R2Tree a
z)

           GutTwo MBR
bl R2Tree a
l MBR
br R2Tree a
r  ->
             MBR -> R2Tree a -> Gut a
forall a. MBR -> R2Tree a -> Gut a
GutOne (MBR -> MBR -> MBR -> MBR -> MBR
union4MBR MBR
bl MBR
br MBR
by MBR
bz) (MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> R2Tree a
forall a.
MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> R2Tree a
Node4 MBR
bl R2Tree a
l MBR
br R2Tree a
r MBR
by R2Tree a
y MBR
bz R2Tree a
z)

    Node4 MBR
ba R2Tree a
a MBR
bb R2Tree a
b MBR
bc R2Tree a
c MBR
bd R2Tree a
d ->
      let !(# MBR
be, R2Tree a
e, !MBR
bw, !R2Tree a
w, !MBR
by, !R2Tree a
y, !MBR
bz, !R2Tree a
z #) = MBR
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> (# MBR, R2Tree a, MBR, R2Tree a, MBR, R2Tree a, MBR, R2Tree a #)
forall a.
MBR
-> MBR
-> a
-> MBR
-> a
-> MBR
-> a
-> MBR
-> a
-> (# MBR, a, MBR, a, MBR, a, MBR, a #)
leastEnlargement4 MBR
bx MBR
ba R2Tree a
a MBR
bb R2Tree a
b MBR
bc R2Tree a
c MBR
bd R2Tree a
d
      in case MBR -> a -> MBR -> R2Tree a -> Gut a
forall a. MBR -> a -> MBR -> R2Tree a -> Gut a
insertGut_ MBR
bx a
x MBR
be R2Tree a
e of
           GutOne MBR
bo R2Tree a
o ->
             MBR -> R2Tree a -> Gut a
forall a. MBR -> R2Tree a -> Gut a
GutOne (MBR -> MBR -> MBR -> MBR -> MBR
union4MBR MBR
bo MBR
bw MBR
by MBR
bz) (MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> R2Tree a
forall a.
MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> R2Tree a
Node4 MBR
bo R2Tree a
o MBR
bw R2Tree a
w MBR
by R2Tree a
y MBR
bz R2Tree a
z)

           GutTwo MBR
bl R2Tree a
l MBR
br R2Tree a
r ->
             case MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> Q3 (R2Tree a)
forall a.
MBR -> a -> MBR -> a -> MBR -> a -> MBR -> a -> MBR -> a -> Q3 a
quadSplit MBR
bl R2Tree a
l MBR
br R2Tree a
r MBR
bw R2Tree a
w MBR
by R2Tree a
y MBR
bz R2Tree a
z of
               Q3L (L3 MBR
bl' MBR
bm R2Tree a
m MBR
bo R2Tree a
o MBR
bp R2Tree a
p) (L2 MBR
br' MBR
bq R2Tree a
q MBR
bs R2Tree a
s) ->
                 MBR -> R2Tree a -> MBR -> R2Tree a -> Gut a
forall a. MBR -> R2Tree a -> MBR -> R2Tree a -> Gut a
GutTwo MBR
bl' (MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
forall a.
MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node3 MBR
bm R2Tree a
m MBR
bo R2Tree a
o MBR
bp R2Tree a
p) MBR
br' (MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
forall a. MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node2 MBR
bq R2Tree a
q MBR
bs R2Tree a
s)

               Q3R (L2 MBR
bl' MBR
bm R2Tree a
m MBR
bo R2Tree a
o) (L3 MBR
br' MBR
bp R2Tree a
p MBR
bq R2Tree a
q MBR
bs R2Tree a
s) ->
                 MBR -> R2Tree a -> MBR -> R2Tree a -> Gut a
forall a. MBR -> R2Tree a -> MBR -> R2Tree a -> Gut a
GutTwo MBR
bl' (MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
forall a. MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node2 MBR
bm R2Tree a
m MBR
bo R2Tree a
o) MBR
br' (MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
forall a.
MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node3 MBR
bp R2Tree a
p MBR
bq R2Tree a
q MBR
bs R2Tree a
s)

    Leaf2 MBR
ba a
a MBR
bb a
b           ->
      MBR -> R2Tree a -> Gut a
forall a. MBR -> R2Tree a -> Gut a
GutOne (MBR -> MBR -> MBR -> MBR
union3MBR MBR
ba MBR
bb MBR
bx) (MBR -> a -> MBR -> a -> MBR -> a -> R2Tree a
forall a. MBR -> a -> MBR -> a -> MBR -> a -> R2Tree a
Leaf3 MBR
ba a
a MBR
bb a
b MBR
bx a
x)

    Leaf3 MBR
ba a
a MBR
bb a
b MBR
bc a
c      ->
      MBR -> R2Tree a -> Gut a
forall a. MBR -> R2Tree a -> Gut a
GutOne (MBR -> MBR -> MBR -> MBR -> MBR
union4MBR MBR
ba MBR
bb MBR
bc MBR
bx) (MBR -> a -> MBR -> a -> MBR -> a -> MBR -> a -> R2Tree a
forall a. MBR -> a -> MBR -> a -> MBR -> a -> MBR -> a -> R2Tree a
Leaf4 MBR
ba a
a MBR
bb a
b MBR
bc a
c MBR
bx a
x)

    Leaf4 MBR
ba a
a MBR
bb a
b MBR
bc a
c MBR
bd a
d ->
      case MBR -> a -> MBR -> a -> MBR -> a -> MBR -> a -> MBR -> a -> Q3 a
forall a.
MBR -> a -> MBR -> a -> MBR -> a -> MBR -> a -> MBR -> a -> Q3 a
quadSplit MBR
ba a
a MBR
bb a
b MBR
bc a
c MBR
bd a
d MBR
bx a
x of
        Q3L (L3 MBR
bl' MBR
bm a
m MBR
bo a
o MBR
bp a
p) (L2 MBR
br' MBR
bq a
q MBR
bs a
s) ->
          MBR -> R2Tree a -> MBR -> R2Tree a -> Gut a
forall a. MBR -> R2Tree a -> MBR -> R2Tree a -> Gut a
GutTwo MBR
bl' (MBR -> a -> MBR -> a -> MBR -> a -> R2Tree a
forall a. MBR -> a -> MBR -> a -> MBR -> a -> R2Tree a
Leaf3 MBR
bm a
m MBR
bo a
o MBR
bp a
p) MBR
br' (MBR -> a -> MBR -> a -> R2Tree a
forall a. MBR -> a -> MBR -> a -> R2Tree a
Leaf2 MBR
bq a
q MBR
bs a
s)

        Q3R (L2 MBR
bl' MBR
bm a
m MBR
bo a
o) (L3 MBR
br' MBR
bp a
p MBR
bq a
q MBR
bs a
s) ->
          MBR -> R2Tree a -> MBR -> R2Tree a -> Gut a
forall a. MBR -> R2Tree a -> MBR -> R2Tree a -> Gut a
GutTwo MBR
bl' (MBR -> a -> MBR -> a -> R2Tree a
forall a. MBR -> a -> MBR -> a -> R2Tree a
Leaf2 MBR
bm a
m MBR
bo a
o) MBR
br' (MBR -> a -> MBR -> a -> MBR -> a -> R2Tree a
forall a. MBR -> a -> MBR -> a -> MBR -> a -> R2Tree a
Leaf3 MBR
bp a
p MBR
bq a
q MBR
bs a
s)

    Leaf1 MBR
ba a
a                ->
      MBR -> R2Tree a -> Gut a
forall a. MBR -> R2Tree a -> Gut a
GutOne (MBR -> MBR -> MBR
unionMBR MBR
ba MBR
bx) (MBR -> a -> MBR -> a -> R2Tree a
forall a. MBR -> a -> MBR -> a -> R2Tree a
Leaf2 MBR
ba a
a MBR
bx a
x)

    R2Tree a
Empty                     ->
      MBR -> R2Tree a -> Gut a
forall a. MBR -> R2Tree a -> Gut a
GutOne MBR
bx (MBR -> a -> R2Tree a
forall a. MBR -> a -> R2Tree a
Leaf1 MBR
bx a
x)


insertGut_ :: MBR -> a -> MBR -> R2Tree a -> Gut a
insertGut_ :: forall a. MBR -> a -> MBR -> R2Tree a -> Gut a
insertGut_ MBR
bx a
x = MBR -> R2Tree a -> Gut a
go
  where
    go :: MBR -> R2Tree a -> Gut a
go MBR
bn R2Tree a
n =
     case R2Tree a
n of
       Node2 MBR
ba R2Tree a
a MBR
bb R2Tree a
b           ->
         let !(# MBR
be, R2Tree a
e, !MBR
bz, !R2Tree a
z #) = MBR
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> (# MBR, R2Tree a, MBR, R2Tree a #)
forall a. MBR -> MBR -> a -> MBR -> a -> (# MBR, a, MBR, a #)
leastEnlargement2 MBR
bx MBR
ba R2Tree a
a MBR
bb R2Tree a
b
         in case MBR -> R2Tree a -> Gut a
go MBR
be R2Tree a
e of
              GutOne MBR
bo R2Tree a
o ->
                MBR -> R2Tree a -> Gut a
forall a. MBR -> R2Tree a -> Gut a
GutOne (MBR -> MBR -> MBR
unionMBR MBR
bo MBR
bz) (MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
forall a. MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node2 MBR
bo R2Tree a
o MBR
bz R2Tree a
z)

              GutTwo MBR
bl R2Tree a
l MBR
br R2Tree a
r ->
                MBR -> R2Tree a -> Gut a
forall a. MBR -> R2Tree a -> Gut a
GutOne (MBR -> MBR -> MBR -> MBR
union3MBR MBR
bl MBR
br MBR
bz) (MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
forall a.
MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node3 MBR
bl R2Tree a
l MBR
br R2Tree a
r MBR
bz R2Tree a
z)

       Node3 MBR
ba R2Tree a
a MBR
bb R2Tree a
b MBR
bc R2Tree a
c      ->
         let !(# MBR
be, R2Tree a
e, !MBR
by, !R2Tree a
y, !MBR
bz, !R2Tree a
z #) = MBR
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> (# MBR, R2Tree a, MBR, R2Tree a, MBR, R2Tree a #)
forall a.
MBR
-> MBR -> a -> MBR -> a -> MBR -> a -> (# MBR, a, MBR, a, MBR, a #)
leastEnlargement3 MBR
bx MBR
ba R2Tree a
a MBR
bb R2Tree a
b MBR
bc R2Tree a
c
         in case MBR -> R2Tree a -> Gut a
go MBR
be R2Tree a
e of
              GutOne MBR
bo R2Tree a
o ->
                MBR -> R2Tree a -> Gut a
forall a. MBR -> R2Tree a -> Gut a
GutOne (MBR -> MBR -> MBR -> MBR
union3MBR MBR
bo MBR
by MBR
bz) (MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
forall a.
MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node3 MBR
bo R2Tree a
o MBR
by R2Tree a
y MBR
bz R2Tree a
z)

              GutTwo MBR
bl R2Tree a
l MBR
br R2Tree a
r  ->
                MBR -> R2Tree a -> Gut a
forall a. MBR -> R2Tree a -> Gut a
GutOne (MBR -> MBR -> MBR -> MBR -> MBR
union4MBR MBR
bl MBR
br MBR
by MBR
bz) (MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> R2Tree a
forall a.
MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> R2Tree a
Node4 MBR
bl R2Tree a
l MBR
br R2Tree a
r MBR
by R2Tree a
y MBR
bz R2Tree a
z)

       Node4 MBR
ba R2Tree a
a MBR
bb R2Tree a
b MBR
bc R2Tree a
c MBR
bd R2Tree a
d ->
         let !(# MBR
be, R2Tree a
e, !MBR
bw, !R2Tree a
w, !MBR
by, !R2Tree a
y, !MBR
bz, !R2Tree a
z #) = MBR
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> (# MBR, R2Tree a, MBR, R2Tree a, MBR, R2Tree a, MBR, R2Tree a #)
forall a.
MBR
-> MBR
-> a
-> MBR
-> a
-> MBR
-> a
-> MBR
-> a
-> (# MBR, a, MBR, a, MBR, a, MBR, a #)
leastEnlargement4 MBR
bx MBR
ba R2Tree a
a MBR
bb R2Tree a
b MBR
bc R2Tree a
c MBR
bd R2Tree a
d
         in case MBR -> R2Tree a -> Gut a
go MBR
be R2Tree a
e of
              GutOne MBR
bo R2Tree a
o ->
                MBR -> R2Tree a -> Gut a
forall a. MBR -> R2Tree a -> Gut a
GutOne (MBR -> MBR -> MBR -> MBR -> MBR
union4MBR MBR
bo MBR
bw MBR
by MBR
bz) (MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> R2Tree a
forall a.
MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> R2Tree a
Node4 MBR
bo R2Tree a
o MBR
bw R2Tree a
w MBR
by R2Tree a
y MBR
bz R2Tree a
z)

              GutTwo MBR
bl R2Tree a
l MBR
br R2Tree a
r ->
                case MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> Q3 (R2Tree a)
forall a.
MBR -> a -> MBR -> a -> MBR -> a -> MBR -> a -> MBR -> a -> Q3 a
quadSplit MBR
bl R2Tree a
l MBR
br R2Tree a
r MBR
bw R2Tree a
w MBR
by R2Tree a
y MBR
bz R2Tree a
z of
                  Q3L (L3 MBR
bl' MBR
bm R2Tree a
m MBR
bo R2Tree a
o MBR
bp R2Tree a
p) (L2 MBR
br' MBR
bq R2Tree a
q MBR
bs R2Tree a
s) ->
                    MBR -> R2Tree a -> MBR -> R2Tree a -> Gut a
forall a. MBR -> R2Tree a -> MBR -> R2Tree a -> Gut a
GutTwo MBR
bl' (MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
forall a.
MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node3 MBR
bm R2Tree a
m MBR
bo R2Tree a
o MBR
bp R2Tree a
p) MBR
br' (MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
forall a. MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node2 MBR
bq R2Tree a
q MBR
bs R2Tree a
s)

                  Q3R (L2 MBR
bl' MBR
bm R2Tree a
m MBR
bo R2Tree a
o) (L3 MBR
br' MBR
bp R2Tree a
p MBR
bq R2Tree a
q MBR
bs R2Tree a
s) ->
                    MBR -> R2Tree a -> MBR -> R2Tree a -> Gut a
forall a. MBR -> R2Tree a -> MBR -> R2Tree a -> Gut a
GutTwo MBR
bl' (MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
forall a. MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node2 MBR
bm R2Tree a
m MBR
bo R2Tree a
o) MBR
br' (MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
forall a.
MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node3 MBR
bp R2Tree a
p MBR
bq R2Tree a
q MBR
bs R2Tree a
s)

       Leaf2 MBR
ba a
a MBR
bb a
b           ->
         MBR -> R2Tree a -> Gut a
forall a. MBR -> R2Tree a -> Gut a
GutOne (MBR -> MBR -> MBR
unionMBR MBR
bn MBR
bx) (MBR -> a -> MBR -> a -> MBR -> a -> R2Tree a
forall a. MBR -> a -> MBR -> a -> MBR -> a -> R2Tree a
Leaf3 MBR
ba a
a MBR
bb a
b MBR
bx a
x)

       Leaf3 MBR
ba a
a MBR
bb a
b MBR
bc a
c      ->
         MBR -> R2Tree a -> Gut a
forall a. MBR -> R2Tree a -> Gut a
GutOne (MBR -> MBR -> MBR
unionMBR MBR
bn MBR
bx) (MBR -> a -> MBR -> a -> MBR -> a -> MBR -> a -> R2Tree a
forall a. MBR -> a -> MBR -> a -> MBR -> a -> MBR -> a -> R2Tree a
Leaf4 MBR
ba a
a MBR
bb a
b MBR
bc a
c MBR
bx a
x)

       Leaf4 MBR
ba a
a MBR
bb a
b MBR
bc a
c MBR
bd a
d ->
         case MBR -> a -> MBR -> a -> MBR -> a -> MBR -> a -> MBR -> a -> Q3 a
forall a.
MBR -> a -> MBR -> a -> MBR -> a -> MBR -> a -> MBR -> a -> Q3 a
quadSplit MBR
ba a
a MBR
bb a
b MBR
bc a
c MBR
bd a
d MBR
bx a
x of
           Q3L (L3 MBR
bl' MBR
bm a
m MBR
bo a
o MBR
bp a
p) (L2 MBR
br' MBR
bq a
q MBR
bs a
s) ->
             MBR -> R2Tree a -> MBR -> R2Tree a -> Gut a
forall a. MBR -> R2Tree a -> MBR -> R2Tree a -> Gut a
GutTwo MBR
bl' (MBR -> a -> MBR -> a -> MBR -> a -> R2Tree a
forall a. MBR -> a -> MBR -> a -> MBR -> a -> R2Tree a
Leaf3 MBR
bm a
m MBR
bo a
o MBR
bp a
p) MBR
br' (MBR -> a -> MBR -> a -> R2Tree a
forall a. MBR -> a -> MBR -> a -> R2Tree a
Leaf2 MBR
bq a
q MBR
bs a
s)

           Q3R (L2 MBR
bl' MBR
bm a
m MBR
bo a
o) (L3 MBR
br' MBR
bp a
p MBR
bq a
q MBR
bs a
s) ->
             MBR -> R2Tree a -> MBR -> R2Tree a -> Gut a
forall a. MBR -> R2Tree a -> MBR -> R2Tree a -> Gut a
GutTwo MBR
bl' (MBR -> a -> MBR -> a -> R2Tree a
forall a. MBR -> a -> MBR -> a -> R2Tree a
Leaf2 MBR
bm a
m MBR
bo a
o) MBR
br' (MBR -> a -> MBR -> a -> MBR -> a -> R2Tree a
forall a. MBR -> a -> MBR -> a -> MBR -> a -> R2Tree a
Leaf3 MBR
bp a
p MBR
bq a
q MBR
bs a
s)

       Leaf1 MBR
ba a
a                ->
         MBR -> R2Tree a -> Gut a
forall a. MBR -> R2Tree a -> Gut a
GutOne (MBR -> MBR -> MBR
unionMBR MBR
ba MBR
bn) (MBR -> a -> MBR -> a -> R2Tree a
forall a. MBR -> a -> MBR -> a -> R2Tree a
Leaf2 MBR
ba a
a MBR
bx a
x)

       R2Tree a
Empty                     ->
         MBR -> R2Tree a -> Gut a
forall a. MBR -> R2Tree a -> Gut a
GutOne MBR
bn (MBR -> a -> R2Tree a
forall a. MBR -> a -> R2Tree a
Leaf1 MBR
bx a
x)



insertGutRootNode :: MBR -> R2Tree a -> Int -> R2Tree a -> Gut a
insertGutRootNode :: forall a. MBR -> R2Tree a -> Int -> R2Tree a -> Gut a
insertGutRootNode MBR
bx R2Tree a
x Int
depth R2Tree a
n =
  case R2Tree a
n of
    Node2 MBR
ba R2Tree a
a MBR
bb R2Tree a
b
      | Int
depth Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
0 ->
          MBR -> R2Tree a -> Gut a
forall a. MBR -> R2Tree a -> Gut a
GutOne (MBR -> MBR -> MBR -> MBR
union3MBR MBR
ba MBR
bb MBR
bx) (MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
forall a.
MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node3 MBR
ba R2Tree a
a MBR
bb R2Tree a
b MBR
bx R2Tree a
x)

      | Bool
otherwise ->
          let !(# MBR
be, R2Tree a
e, !MBR
bz, !R2Tree a
z #) = MBR
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> (# MBR, R2Tree a, MBR, R2Tree a #)
forall a. MBR -> MBR -> a -> MBR -> a -> (# MBR, a, MBR, a #)
leastEnlargement2 MBR
bx MBR
ba R2Tree a
a MBR
bb R2Tree a
b
          in case MBR -> R2Tree a -> Int -> MBR -> R2Tree a -> Gut a
forall a. MBR -> R2Tree a -> Int -> MBR -> R2Tree a -> Gut a
insertGutNode MBR
bx R2Tree a
x (Int
depth Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) MBR
be R2Tree a
e of
               GutOne MBR
bo R2Tree a
o ->
                 MBR -> R2Tree a -> Gut a
forall a. MBR -> R2Tree a -> Gut a
GutOne (MBR -> MBR -> MBR
unionMBR MBR
bo MBR
bz) (MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
forall a. MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node2 MBR
bo R2Tree a
o MBR
bz R2Tree a
z)

               GutTwo MBR
bl R2Tree a
l MBR
br R2Tree a
r ->
                 MBR -> R2Tree a -> Gut a
forall a. MBR -> R2Tree a -> Gut a
GutOne (MBR -> MBR -> MBR -> MBR
union3MBR MBR
bl MBR
br MBR
bz) (MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
forall a.
MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node3 MBR
bl R2Tree a
l MBR
br R2Tree a
r MBR
bz R2Tree a
z)

    Node3 MBR
ba R2Tree a
a MBR
bb R2Tree a
b MBR
bc R2Tree a
c
      | Int
depth Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
0 ->
          MBR -> R2Tree a -> Gut a
forall a. MBR -> R2Tree a -> Gut a
GutOne (MBR -> MBR -> MBR -> MBR -> MBR
union4MBR MBR
ba MBR
bb MBR
bc MBR
bx) (MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> R2Tree a
forall a.
MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> R2Tree a
Node4 MBR
ba R2Tree a
a MBR
bb R2Tree a
b MBR
bc R2Tree a
c MBR
bx R2Tree a
x)

      | Bool
otherwise ->
          let !(# MBR
be, R2Tree a
e, !MBR
by, !R2Tree a
y, !MBR
bz, !R2Tree a
z #) = MBR
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> (# MBR, R2Tree a, MBR, R2Tree a, MBR, R2Tree a #)
forall a.
MBR
-> MBR -> a -> MBR -> a -> MBR -> a -> (# MBR, a, MBR, a, MBR, a #)
leastEnlargement3 MBR
bx MBR
ba R2Tree a
a MBR
bb R2Tree a
b MBR
bc R2Tree a
c
          in case MBR -> R2Tree a -> Int -> MBR -> R2Tree a -> Gut a
forall a. MBR -> R2Tree a -> Int -> MBR -> R2Tree a -> Gut a
insertGutNode MBR
bx R2Tree a
x (Int
depth Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) MBR
be R2Tree a
e of
               GutOne MBR
bo R2Tree a
o ->
                 MBR -> R2Tree a -> Gut a
forall a. MBR -> R2Tree a -> Gut a
GutOne (MBR -> MBR -> MBR -> MBR
union3MBR MBR
bo MBR
by MBR
bz) (MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
forall a.
MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node3 MBR
bo R2Tree a
o MBR
by R2Tree a
y MBR
bz R2Tree a
z)

               GutTwo MBR
bl R2Tree a
l MBR
br R2Tree a
r  ->
                 MBR -> R2Tree a -> Gut a
forall a. MBR -> R2Tree a -> Gut a
GutOne (MBR -> MBR -> MBR -> MBR -> MBR
union4MBR MBR
bl MBR
br MBR
by MBR
bz) (MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> R2Tree a
forall a.
MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> R2Tree a
Node4 MBR
bl R2Tree a
l MBR
br R2Tree a
r MBR
by R2Tree a
y MBR
bz R2Tree a
z)

    Node4 MBR
ba R2Tree a
a MBR
bb R2Tree a
b MBR
bc R2Tree a
c MBR
bd R2Tree a
d
      | Int
depth Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
0 ->
          case MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> Q3 (R2Tree a)
forall a.
MBR -> a -> MBR -> a -> MBR -> a -> MBR -> a -> MBR -> a -> Q3 a
quadSplit MBR
ba R2Tree a
a MBR
bb R2Tree a
b MBR
bc R2Tree a
c MBR
bd R2Tree a
d MBR
bx R2Tree a
x of
            Q3L (L3 MBR
bl' MBR
bm R2Tree a
m MBR
bo R2Tree a
o MBR
bp R2Tree a
p) (L2 MBR
br' MBR
bq R2Tree a
q MBR
bs R2Tree a
s) ->
              MBR -> R2Tree a -> MBR -> R2Tree a -> Gut a
forall a. MBR -> R2Tree a -> MBR -> R2Tree a -> Gut a
GutTwo MBR
bl' (MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
forall a.
MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node3 MBR
bm R2Tree a
m MBR
bo R2Tree a
o MBR
bp R2Tree a
p) MBR
br' (MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
forall a. MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node2 MBR
bq R2Tree a
q MBR
bs R2Tree a
s)

            Q3R (L2 MBR
bl' MBR
bm R2Tree a
m MBR
bo R2Tree a
o) (L3 MBR
br' MBR
bp R2Tree a
p MBR
bq R2Tree a
q MBR
bs R2Tree a
s) ->
              MBR -> R2Tree a -> MBR -> R2Tree a -> Gut a
forall a. MBR -> R2Tree a -> MBR -> R2Tree a -> Gut a
GutTwo MBR
bl' (MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
forall a. MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node2 MBR
bm R2Tree a
m MBR
bo R2Tree a
o) MBR
br' (MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
forall a.
MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node3 MBR
bp R2Tree a
p MBR
bq R2Tree a
q MBR
bs R2Tree a
s)

      | Bool
otherwise ->
          let !(# MBR
be, R2Tree a
e, !MBR
bw, !R2Tree a
w, !MBR
by, !R2Tree a
y, !MBR
bz, !R2Tree a
z #) = MBR
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> (# MBR, R2Tree a, MBR, R2Tree a, MBR, R2Tree a, MBR, R2Tree a #)
forall a.
MBR
-> MBR
-> a
-> MBR
-> a
-> MBR
-> a
-> MBR
-> a
-> (# MBR, a, MBR, a, MBR, a, MBR, a #)
leastEnlargement4 MBR
bx MBR
ba R2Tree a
a MBR
bb R2Tree a
b MBR
bc R2Tree a
c MBR
bd R2Tree a
d
          in case MBR -> R2Tree a -> Int -> MBR -> R2Tree a -> Gut a
forall a. MBR -> R2Tree a -> Int -> MBR -> R2Tree a -> Gut a
insertGutNode MBR
bx R2Tree a
x (Int
depth Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) MBR
be R2Tree a
e of
               GutOne MBR
bo R2Tree a
o ->
                 MBR -> R2Tree a -> Gut a
forall a. MBR -> R2Tree a -> Gut a
GutOne (MBR -> MBR -> MBR -> MBR -> MBR
union4MBR MBR
bo MBR
bw MBR
by MBR
bz) (MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> R2Tree a
forall a.
MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> R2Tree a
Node4 MBR
bo R2Tree a
o MBR
bw R2Tree a
w MBR
by R2Tree a
y MBR
bz R2Tree a
z)

               GutTwo MBR
bl R2Tree a
l MBR
br R2Tree a
r ->
                 case MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> Q3 (R2Tree a)
forall a.
MBR -> a -> MBR -> a -> MBR -> a -> MBR -> a -> MBR -> a -> Q3 a
quadSplit MBR
bl R2Tree a
l MBR
br R2Tree a
r MBR
bw R2Tree a
w MBR
by R2Tree a
y MBR
bz R2Tree a
z of
                   Q3L (L3 MBR
bl' MBR
bm R2Tree a
m MBR
bo R2Tree a
o MBR
bp R2Tree a
p) (L2 MBR
br' MBR
bq R2Tree a
q MBR
bs R2Tree a
s) ->
                     MBR -> R2Tree a -> MBR -> R2Tree a -> Gut a
forall a. MBR -> R2Tree a -> MBR -> R2Tree a -> Gut a
GutTwo MBR
bl' (MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
forall a.
MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node3 MBR
bm R2Tree a
m MBR
bo R2Tree a
o MBR
bp R2Tree a
p) MBR
br' (MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
forall a. MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node2 MBR
bq R2Tree a
q MBR
bs R2Tree a
s)

                   Q3R (L2 MBR
bl' MBR
bm R2Tree a
m MBR
bo R2Tree a
o) (L3 MBR
br' MBR
bp R2Tree a
p MBR
bq R2Tree a
q MBR
bs R2Tree a
s) ->
                     MBR -> R2Tree a -> MBR -> R2Tree a -> Gut a
forall a. MBR -> R2Tree a -> MBR -> R2Tree a -> Gut a
GutTwo MBR
bl' (MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
forall a. MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node2 MBR
bm R2Tree a
m MBR
bo R2Tree a
o) MBR
br' (MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
forall a.
MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node3 MBR
bp R2Tree a
p MBR
bq R2Tree a
q MBR
bs R2Tree a
s)

    R2Tree a
_ -> String -> Gut a
forall a. String -> a
errorWithoutStackTrace String
"Data.R2Tree.Double.Internal.insertGutRootNode: reached a leaf"

insertGutNode :: MBR -> R2Tree a -> Int -> MBR -> R2Tree a -> Gut a
insertGutNode :: forall a. MBR -> R2Tree a -> Int -> MBR -> R2Tree a -> Gut a
insertGutNode MBR
bx R2Tree a
x = Int -> MBR -> R2Tree a -> Gut a
forall {a}. (Ord a, Num a) => a -> MBR -> R2Tree a -> Gut a
go
  where
    go :: a -> MBR -> R2Tree a -> Gut a
go a
depth MBR
bn R2Tree a
n =
      case R2Tree a
n of
        Node2 MBR
ba R2Tree a
a MBR
bb R2Tree a
b
          | a
depth a -> a -> Bool
forall a. Ord a => a -> a -> Bool
<= a
0 ->
              MBR -> R2Tree a -> Gut a
forall a. MBR -> R2Tree a -> Gut a
GutOne (MBR -> MBR -> MBR
unionMBR MBR
bn MBR
bx) (MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
forall a.
MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node3 MBR
ba R2Tree a
a MBR
bb R2Tree a
b MBR
bx R2Tree a
x)

          | Bool
otherwise ->
              let !(# MBR
be, R2Tree a
e, !MBR
bz, !R2Tree a
z #) = MBR
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> (# MBR, R2Tree a, MBR, R2Tree a #)
forall a. MBR -> MBR -> a -> MBR -> a -> (# MBR, a, MBR, a #)
leastEnlargement2 MBR
bx MBR
ba R2Tree a
a MBR
bb R2Tree a
b
              in case a -> MBR -> R2Tree a -> Gut a
go (a
depth a -> a -> a
forall a. Num a => a -> a -> a
- a
1) MBR
be R2Tree a
e of
                   GutOne MBR
bo R2Tree a
o ->
                     MBR -> R2Tree a -> Gut a
forall a. MBR -> R2Tree a -> Gut a
GutOne (MBR -> MBR -> MBR
unionMBR MBR
bo MBR
bz) (MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
forall a. MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node2 MBR
bo R2Tree a
o MBR
bz R2Tree a
z)

                   GutTwo MBR
bl R2Tree a
l MBR
br R2Tree a
r ->
                     MBR -> R2Tree a -> Gut a
forall a. MBR -> R2Tree a -> Gut a
GutOne (MBR -> MBR -> MBR -> MBR
union3MBR MBR
bl MBR
br MBR
bz) (MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
forall a.
MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node3 MBR
bl R2Tree a
l MBR
br R2Tree a
r MBR
bz R2Tree a
z)

        Node3 MBR
ba R2Tree a
a MBR
bb R2Tree a
b MBR
bc R2Tree a
c
          | a
depth a -> a -> Bool
forall a. Ord a => a -> a -> Bool
<= a
0 ->
              MBR -> R2Tree a -> Gut a
forall a. MBR -> R2Tree a -> Gut a
GutOne (MBR -> MBR -> MBR
unionMBR MBR
bn MBR
bx) (MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> R2Tree a
forall a.
MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> R2Tree a
Node4 MBR
ba R2Tree a
a MBR
bb R2Tree a
b MBR
bc R2Tree a
c MBR
bx R2Tree a
x)

          | Bool
otherwise ->
              let !(# MBR
be, R2Tree a
e, !MBR
by, !R2Tree a
y, !MBR
bz, !R2Tree a
z #) = MBR
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> (# MBR, R2Tree a, MBR, R2Tree a, MBR, R2Tree a #)
forall a.
MBR
-> MBR -> a -> MBR -> a -> MBR -> a -> (# MBR, a, MBR, a, MBR, a #)
leastEnlargement3 MBR
bx MBR
ba R2Tree a
a MBR
bb R2Tree a
b MBR
bc R2Tree a
c
              in case a -> MBR -> R2Tree a -> Gut a
go (a
depth a -> a -> a
forall a. Num a => a -> a -> a
- a
1) MBR
be R2Tree a
e of
                   GutOne MBR
bo R2Tree a
o ->
                     MBR -> R2Tree a -> Gut a
forall a. MBR -> R2Tree a -> Gut a
GutOne (MBR -> MBR -> MBR -> MBR
union3MBR MBR
bo MBR
by MBR
bz) (MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
forall a.
MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node3 MBR
bo R2Tree a
o MBR
by R2Tree a
y MBR
bz R2Tree a
z)

                   GutTwo MBR
bl R2Tree a
l MBR
br R2Tree a
r  ->
                     MBR -> R2Tree a -> Gut a
forall a. MBR -> R2Tree a -> Gut a
GutOne (MBR -> MBR -> MBR -> MBR -> MBR
union4MBR MBR
bl MBR
br MBR
by MBR
bz) (MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> R2Tree a
forall a.
MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> R2Tree a
Node4 MBR
bl R2Tree a
l MBR
br R2Tree a
r MBR
by R2Tree a
y MBR
bz R2Tree a
z)

        Node4 MBR
ba R2Tree a
a MBR
bb R2Tree a
b MBR
bc R2Tree a
c MBR
bd R2Tree a
d
          | a
depth a -> a -> Bool
forall a. Ord a => a -> a -> Bool
<= a
0 ->
              case MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> Q3 (R2Tree a)
forall a.
MBR -> a -> MBR -> a -> MBR -> a -> MBR -> a -> MBR -> a -> Q3 a
quadSplit MBR
ba R2Tree a
a MBR
bb R2Tree a
b MBR
bc R2Tree a
c MBR
bd R2Tree a
d MBR
bx R2Tree a
x of
                Q3L (L3 MBR
bl' MBR
bm R2Tree a
m MBR
bo R2Tree a
o MBR
bp R2Tree a
p) (L2 MBR
br' MBR
bq R2Tree a
q MBR
bs R2Tree a
s) ->
                  MBR -> R2Tree a -> MBR -> R2Tree a -> Gut a
forall a. MBR -> R2Tree a -> MBR -> R2Tree a -> Gut a
GutTwo MBR
bl' (MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
forall a.
MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node3 MBR
bm R2Tree a
m MBR
bo R2Tree a
o MBR
bp R2Tree a
p) MBR
br' (MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
forall a. MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node2 MBR
bq R2Tree a
q MBR
bs R2Tree a
s)

                Q3R (L2 MBR
bl' MBR
bm R2Tree a
m MBR
bo R2Tree a
o) (L3 MBR
br' MBR
bp R2Tree a
p MBR
bq R2Tree a
q MBR
bs R2Tree a
s) ->
                  MBR -> R2Tree a -> MBR -> R2Tree a -> Gut a
forall a. MBR -> R2Tree a -> MBR -> R2Tree a -> Gut a
GutTwo MBR
bl' (MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
forall a. MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node2 MBR
bm R2Tree a
m MBR
bo R2Tree a
o) MBR
br' (MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
forall a.
MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node3 MBR
bp R2Tree a
p MBR
bq R2Tree a
q MBR
bs R2Tree a
s)

          | Bool
otherwise ->
              let !(# MBR
be, R2Tree a
e, !MBR
bw, !R2Tree a
w, !MBR
by, !R2Tree a
y, !MBR
bz, !R2Tree a
z #) = MBR
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> (# MBR, R2Tree a, MBR, R2Tree a, MBR, R2Tree a, MBR, R2Tree a #)
forall a.
MBR
-> MBR
-> a
-> MBR
-> a
-> MBR
-> a
-> MBR
-> a
-> (# MBR, a, MBR, a, MBR, a, MBR, a #)
leastEnlargement4 MBR
bx MBR
ba R2Tree a
a MBR
bb R2Tree a
b MBR
bc R2Tree a
c MBR
bd R2Tree a
d
              in case a -> MBR -> R2Tree a -> Gut a
go (a
depth a -> a -> a
forall a. Num a => a -> a -> a
- a
1) MBR
be R2Tree a
e of
                   GutOne MBR
bo R2Tree a
o ->
                     MBR -> R2Tree a -> Gut a
forall a. MBR -> R2Tree a -> Gut a
GutOne (MBR -> MBR -> MBR -> MBR -> MBR
union4MBR MBR
bo MBR
bw MBR
by MBR
bz) (MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> R2Tree a
forall a.
MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> R2Tree a
Node4 MBR
bo R2Tree a
o MBR
bw R2Tree a
w MBR
by R2Tree a
y MBR
bz R2Tree a
z)

                   GutTwo MBR
bl R2Tree a
l MBR
br R2Tree a
r ->
                     case MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> Q3 (R2Tree a)
forall a.
MBR -> a -> MBR -> a -> MBR -> a -> MBR -> a -> MBR -> a -> Q3 a
quadSplit MBR
bl R2Tree a
l MBR
br R2Tree a
r MBR
bw R2Tree a
w MBR
by R2Tree a
y MBR
bz R2Tree a
z of
                       Q3L (L3 MBR
bl' MBR
bm R2Tree a
m MBR
bo R2Tree a
o MBR
bp R2Tree a
p) (L2 MBR
br' MBR
bq R2Tree a
q MBR
bs R2Tree a
s) ->
                         MBR -> R2Tree a -> MBR -> R2Tree a -> Gut a
forall a. MBR -> R2Tree a -> MBR -> R2Tree a -> Gut a
GutTwo MBR
bl' (MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
forall a.
MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node3 MBR
bm R2Tree a
m MBR
bo R2Tree a
o MBR
bp R2Tree a
p) MBR
br' (MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
forall a. MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node2 MBR
bq R2Tree a
q MBR
bs R2Tree a
s)

                       Q3R (L2 MBR
bl' MBR
bm R2Tree a
m MBR
bo R2Tree a
o) (L3 MBR
br' MBR
bp R2Tree a
p MBR
bq R2Tree a
q MBR
bs R2Tree a
s) ->
                         MBR -> R2Tree a -> MBR -> R2Tree a -> Gut a
forall a. MBR -> R2Tree a -> MBR -> R2Tree a -> Gut a
GutTwo MBR
bl' (MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
forall a. MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node2 MBR
bm R2Tree a
m MBR
bo R2Tree a
o) MBR
br' (MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
forall a.
MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node3 MBR
bp R2Tree a
p MBR
bq R2Tree a
q MBR
bs R2Tree a
s)

        R2Tree a
_ -> String -> Gut a
forall a. String -> a
errorWithoutStackTrace String
"Data.R2Tree.Double.Internal.insertGutNode: reached a leaf"



{-# INLINE enlargement #-}
-- as in (adding A to B)
enlargement :: MBR -> MBR -> Double
enlargement :: MBR -> MBR -> Double
enlargement MBR
bx MBR
ba = MBR -> Double
areaMBR (MBR -> MBR -> MBR
unionMBR MBR
ba MBR
bx) Double -> Double -> Double
forall a. Num a => a -> a -> a
- MBR -> Double
areaMBR MBR
ba

leastEnlargement2 :: MBR -> MBR -> a -> MBR -> a -> (# MBR, a, MBR, a #)
leastEnlargement2 :: forall a. MBR -> MBR -> a -> MBR -> a -> (# MBR, a, MBR, a #)
leastEnlargement2 MBR
bx MBR
ba a
a MBR
bb a
b =
  let aw :: (# MBR, a, MBR, a #)
aw = (# MBR
ba, a
a, MBR
bb, a
b #)
      bw :: (# MBR, a, MBR, a #)
bw = (# MBR
bb, a
b, MBR
ba, a
a #)

  in case MBR -> MBR -> Double
enlargement MBR
bx MBR
ba Double -> Double -> Ordering
forall a. Ord a => a -> a -> Ordering
`compare` MBR -> MBR -> Double
enlargement MBR
bx MBR
bb of
       Ordering
GT -> (# MBR, a, MBR, a #)
bw
       Ordering
LT -> (# MBR, a, MBR, a #)
aw
       Ordering
EQ | MBR -> Double
areaMBR MBR
ba Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
<= MBR -> Double
areaMBR MBR
bb -> (# MBR, a, MBR, a #)
aw
          | Bool
otherwise                -> (# MBR, a, MBR, a #)
bw

leastEnlargement3
  :: MBR -> MBR -> a -> MBR -> a -> MBR -> a -> (# MBR, a, MBR, a, MBR, a #)
leastEnlargement3 :: forall a.
MBR
-> MBR -> a -> MBR -> a -> MBR -> a -> (# MBR, a, MBR, a, MBR, a #)
leastEnlargement3 MBR
bx MBR
ba a
a MBR
bb a
b MBR
bc a
c =
  let aw :: (# MBR, a, MBR, a, MBR, a #)
aw = let !(# MBR
be, a
e, MBR
by, a
y #) = MBR -> MBR -> a -> MBR -> a -> (# MBR, a, MBR, a #)
forall a. MBR -> MBR -> a -> MBR -> a -> (# MBR, a, MBR, a #)
leastEnlargement2 MBR
bx MBR
ba a
a MBR
bc a
c
           in (# MBR
be, a
e, MBR
by, a
y, MBR
bb, a
b #)

      bw :: (# MBR, a, MBR, a, MBR, a #)
bw = let !(# MBR
be, a
e, MBR
by, a
y #) = MBR -> MBR -> a -> MBR -> a -> (# MBR, a, MBR, a #)
forall a. MBR -> MBR -> a -> MBR -> a -> (# MBR, a, MBR, a #)
leastEnlargement2 MBR
bx MBR
bb a
b MBR
bc a
c
           in (# MBR
be, a
e, MBR
by, a
y, MBR
ba, a
a #)

  in case MBR -> MBR -> Double
enlargement MBR
bx MBR
ba Double -> Double -> Ordering
forall a. Ord a => a -> a -> Ordering
`compare` MBR -> MBR -> Double
enlargement MBR
bx MBR
bb of
       Ordering
GT -> (# MBR, a, MBR, a, MBR, a #)
bw
       Ordering
LT -> (# MBR, a, MBR, a, MBR, a #)
aw
       Ordering
EQ | MBR -> Double
areaMBR MBR
ba Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
<= MBR -> Double
areaMBR MBR
bb -> (# MBR, a, MBR, a, MBR, a #)
aw
          | Bool
otherwise                -> (# MBR, a, MBR, a, MBR, a #)
bw

leastEnlargement4
  :: MBR -> MBR -> a -> MBR -> a -> MBR -> a -> MBR -> a
  -> (# MBR, a, MBR, a, MBR, a, MBR, a #)
leastEnlargement4 :: forall a.
MBR
-> MBR
-> a
-> MBR
-> a
-> MBR
-> a
-> MBR
-> a
-> (# MBR, a, MBR, a, MBR, a, MBR, a #)
leastEnlargement4 MBR
bx MBR
ba a
a MBR
bb a
b MBR
bc a
c MBR
bd a
d =
  let !(# MBR
be, a
e, MBR
bn, a
n #) = MBR -> MBR -> a -> MBR -> a -> (# MBR, a, MBR, a #)
forall a. MBR -> MBR -> a -> MBR -> a -> (# MBR, a, MBR, a #)
leastEnlargement2 MBR
bx MBR
ba a
a MBR
bb a
b
      !(# MBR
bf, a
f, MBR
bo, a
o #) = MBR -> MBR -> a -> MBR -> a -> (# MBR, a, MBR, a #)
forall a. MBR -> MBR -> a -> MBR -> a -> (# MBR, a, MBR, a #)
leastEnlargement2 MBR
bx MBR
bc a
c MBR
bd a
d
      !(# MBR
bg, a
g, MBR
bp, a
p #) = MBR -> MBR -> a -> MBR -> a -> (# MBR, a, MBR, a #)
forall a. MBR -> MBR -> a -> MBR -> a -> (# MBR, a, MBR, a #)
leastEnlargement2 MBR
bx MBR
be a
e MBR
bf a
f

  in (# MBR
bg, a
g, MBR
bn, a
n, MBR
bo, a
o, MBR
bp, a
p #)



data L2 a = L2 !MBR !MBR a !MBR a

data L3 a = L3 !MBR !MBR a !MBR a !MBR a

data Q1 a = Q1L !(L2 a) !MBR a
          | Q1R !MBR a !(L2 a)

data Q2 a = Q2L !(L3 a) !MBR a
          | Q2M !(L2 a) !(L2 a)
          | Q2R !MBR a !(L3 a)

data Q3 a = Q3L !(L3 a) !(L2 a)
          | Q3R !(L2 a) !(L3 a)



quadSplit :: MBR -> a -> MBR -> a -> MBR -> a -> MBR -> a -> MBR -> a -> Q3 a
quadSplit :: forall a.
MBR -> a -> MBR -> a -> MBR -> a -> MBR -> a -> MBR -> a -> Q3 a
quadSplit MBR
ba a
a MBR
bb a
b MBR
bc a
c MBR
bd a
d MBR
be a
e =
  let !(# MBR
bl, a
l, MBR
br, a
r, MBR
bx, a
x, MBR
by, a
y, MBR
bz, a
z #) = MBR
-> a
-> MBR
-> a
-> MBR
-> a
-> MBR
-> a
-> MBR
-> a
-> (# MBR, a, MBR, a, MBR, a, MBR, a, MBR, a #)
forall a.
MBR
-> a
-> MBR
-> a
-> MBR
-> a
-> MBR
-> a
-> MBR
-> a
-> (# MBR, a, MBR, a, MBR, a, MBR, a, MBR, a #)
pickSeeds MBR
ba a
a MBR
bb a
b MBR
bc a
c MBR
bd a
d MBR
be a
e
      !(# Q1 a
q1, MBR
bv, a
v, MBR
bw, a
w #) = MBR
-> a
-> MBR
-> a
-> MBR
-> a
-> MBR
-> a
-> MBR
-> a
-> (# Q1 a, MBR, a, MBR, a #)
forall a.
MBR
-> a
-> MBR
-> a
-> MBR
-> a
-> MBR
-> a
-> MBR
-> a
-> (# Q1 a, MBR, a, MBR, a #)
distribute3 MBR
bl a
l MBR
br a
r MBR
bx a
x MBR
by a
y MBR
bz a
z
      !(# Q2 a
q2, MBR
bu, a
u #) = Q1 a -> MBR -> a -> MBR -> a -> (# Q2 a, MBR, a #)
forall a. Q1 a -> MBR -> a -> MBR -> a -> (# Q2 a, MBR, a #)
distribute2 Q1 a
q1 MBR
bv a
v MBR
bw a
w

  in Q2 a -> MBR -> a -> Q3 a
forall a. Q2 a -> MBR -> a -> Q3 a
distribute1 Q2 a
q2 MBR
bu a
u



pickSeeds
  :: MBR -> a -> MBR -> a -> MBR -> a -> MBR -> a -> MBR -> a
  -> (# MBR, a, MBR, a, MBR, a, MBR, a, MBR, a #)
pickSeeds :: forall a.
MBR
-> a
-> MBR
-> a
-> MBR
-> a
-> MBR
-> a
-> MBR
-> a
-> (# MBR, a, MBR, a, MBR, a, MBR, a, MBR, a #)
pickSeeds MBR
ba a
a MBR
bb a
b MBR
bc a
c MBR
bd a
d MBR
be a
e =
  let waste :: MBR -> MBR -> Double
waste MBR
bx MBR
by = MBR -> Double
areaMBR (MBR -> MBR -> MBR
unionMBR MBR
bx MBR
by) Double -> Double -> Double
forall a. Num a => a -> a -> a
- MBR -> Double
areaMBR MBR
bx Double -> Double -> Double
forall a. Num a => a -> a -> a
- MBR -> Double
areaMBR MBR
by

      align :: (# MBR, b, MBR, d, e, f, g, h, i, j #)
-> (# MBR, b, MBR, d, e, f, g, h, i, j #)
-> (# MBR, b, MBR, d, e, f, g, h, i, j #)
align x :: (# MBR, b, MBR, d, e, f, g, h, i, j #)
x@(# MBR
bw, b
_, MBR
bx, d
_, e
_, f
_, g
_, h
_, i
_, j
_ #)
            y :: (# MBR, b, MBR, d, e, f, g, h, i, j #)
y@(# MBR
by, b
_, MBR
bz, d
_, e
_, f
_, g
_, h
_, i
_, j
_ #)
        | MBR -> MBR -> Double
waste MBR
bw MBR
bx Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
> MBR -> MBR -> Double
waste MBR
by MBR
bz = (# MBR, b, MBR, d, e, f, g, h, i, j #)
x
        | Bool
otherwise                 = (# MBR, b, MBR, d, e, f, g, h, i, j #)
y

  in (# MBR, a, MBR, a, MBR, a, MBR, a, MBR, a #)
-> (# MBR, a, MBR, a, MBR, a, MBR, a, MBR, a #)
-> (# MBR, a, MBR, a, MBR, a, MBR, a, MBR, a #)
forall {b} {d} {e} {f} {g} {h} {i} {j}.
(# MBR, b, MBR, d, e, f, g, h, i, j #)
-> (# MBR, b, MBR, d, e, f, g, h, i, j #)
-> (# MBR, b, MBR, d, e, f, g, h, i, j #)
align (# MBR
ba, a
a, MBR
bb, a
b, MBR
bc, a
c, MBR
bd, a
d, MBR
be, a
e #)
   ( (# MBR, a, MBR, a, MBR, a, MBR, a, MBR, a #)
-> (# MBR, a, MBR, a, MBR, a, MBR, a, MBR, a #)
-> (# MBR, a, MBR, a, MBR, a, MBR, a, MBR, a #)
forall {b} {d} {e} {f} {g} {h} {i} {j}.
(# MBR, b, MBR, d, e, f, g, h, i, j #)
-> (# MBR, b, MBR, d, e, f, g, h, i, j #)
-> (# MBR, b, MBR, d, e, f, g, h, i, j #)
align (# MBR
ba, a
a, MBR
bc, a
c, MBR
bb, a
b, MBR
bd, a
d, MBR
be, a
e #)
   ( (# MBR, a, MBR, a, MBR, a, MBR, a, MBR, a #)
-> (# MBR, a, MBR, a, MBR, a, MBR, a, MBR, a #)
-> (# MBR, a, MBR, a, MBR, a, MBR, a, MBR, a #)
forall {b} {d} {e} {f} {g} {h} {i} {j}.
(# MBR, b, MBR, d, e, f, g, h, i, j #)
-> (# MBR, b, MBR, d, e, f, g, h, i, j #)
-> (# MBR, b, MBR, d, e, f, g, h, i, j #)
align (# MBR
ba, a
a, MBR
bd, a
d, MBR
bb, a
b, MBR
bc, a
c, MBR
be, a
e #)
   ( (# MBR, a, MBR, a, MBR, a, MBR, a, MBR, a #)
-> (# MBR, a, MBR, a, MBR, a, MBR, a, MBR, a #)
-> (# MBR, a, MBR, a, MBR, a, MBR, a, MBR, a #)
forall {b} {d} {e} {f} {g} {h} {i} {j}.
(# MBR, b, MBR, d, e, f, g, h, i, j #)
-> (# MBR, b, MBR, d, e, f, g, h, i, j #)
-> (# MBR, b, MBR, d, e, f, g, h, i, j #)
align (# MBR
ba, a
a, MBR
be, a
e, MBR
bb, a
b, MBR
bc, a
c, MBR
bd, a
d #)
   ( (# MBR, a, MBR, a, MBR, a, MBR, a, MBR, a #)
-> (# MBR, a, MBR, a, MBR, a, MBR, a, MBR, a #)
-> (# MBR, a, MBR, a, MBR, a, MBR, a, MBR, a #)
forall {b} {d} {e} {f} {g} {h} {i} {j}.
(# MBR, b, MBR, d, e, f, g, h, i, j #)
-> (# MBR, b, MBR, d, e, f, g, h, i, j #)
-> (# MBR, b, MBR, d, e, f, g, h, i, j #)
align (# MBR
bb, a
b, MBR
bc, a
c, MBR
ba, a
a, MBR
bd, a
d, MBR
be, a
e #)
   ( (# MBR, a, MBR, a, MBR, a, MBR, a, MBR, a #)
-> (# MBR, a, MBR, a, MBR, a, MBR, a, MBR, a #)
-> (# MBR, a, MBR, a, MBR, a, MBR, a, MBR, a #)
forall {b} {d} {e} {f} {g} {h} {i} {j}.
(# MBR, b, MBR, d, e, f, g, h, i, j #)
-> (# MBR, b, MBR, d, e, f, g, h, i, j #)
-> (# MBR, b, MBR, d, e, f, g, h, i, j #)
align (# MBR
bb, a
b, MBR
bd, a
d, MBR
ba, a
a, MBR
bc, a
c, MBR
be, a
e #)
   ( (# MBR, a, MBR, a, MBR, a, MBR, a, MBR, a #)
-> (# MBR, a, MBR, a, MBR, a, MBR, a, MBR, a #)
-> (# MBR, a, MBR, a, MBR, a, MBR, a, MBR, a #)
forall {b} {d} {e} {f} {g} {h} {i} {j}.
(# MBR, b, MBR, d, e, f, g, h, i, j #)
-> (# MBR, b, MBR, d, e, f, g, h, i, j #)
-> (# MBR, b, MBR, d, e, f, g, h, i, j #)
align (# MBR
bb, a
b, MBR
be, a
e, MBR
ba, a
a, MBR
bc, a
c, MBR
bd, a
d #)
   ( (# MBR, a, MBR, a, MBR, a, MBR, a, MBR, a #)
-> (# MBR, a, MBR, a, MBR, a, MBR, a, MBR, a #)
-> (# MBR, a, MBR, a, MBR, a, MBR, a, MBR, a #)
forall {b} {d} {e} {f} {g} {h} {i} {j}.
(# MBR, b, MBR, d, e, f, g, h, i, j #)
-> (# MBR, b, MBR, d, e, f, g, h, i, j #)
-> (# MBR, b, MBR, d, e, f, g, h, i, j #)
align (# MBR
bc, a
c, MBR
bd, a
d, MBR
ba, a
a, MBR
bb, a
b, MBR
be, a
e #)
   ( (# MBR, a, MBR, a, MBR, a, MBR, a, MBR, a #)
-> (# MBR, a, MBR, a, MBR, a, MBR, a, MBR, a #)
-> (# MBR, a, MBR, a, MBR, a, MBR, a, MBR, a #)
forall {b} {d} {e} {f} {g} {h} {i} {j}.
(# MBR, b, MBR, d, e, f, g, h, i, j #)
-> (# MBR, b, MBR, d, e, f, g, h, i, j #)
-> (# MBR, b, MBR, d, e, f, g, h, i, j #)
align (# MBR
bc, a
c, MBR
be, a
e, MBR
ba, a
a, MBR
bb, a
b, MBR
bd, a
d #)
           (# MBR
bd, a
d, MBR
be, a
e, MBR
ba, a
a, MBR
bb, a
b, MBR
bc, a
c #) ))))))))



distribute3
  :: MBR -> a -> MBR -> a -> MBR -> a -> MBR -> a -> MBR -> a -> (# Q1 a, MBR, a, MBR, a #)
distribute3 :: forall a.
MBR
-> a
-> MBR
-> a
-> MBR
-> a
-> MBR
-> a
-> MBR
-> a
-> (# Q1 a, MBR, a, MBR, a #)
distribute3 MBR
bl a
l MBR
br a
r MBR
bx a
x MBR
by a
y MBR
bz a
z =
  let delta :: MBR -> Double
delta MBR
ba = Double -> Double
forall a. Num a => a -> a
abs (MBR -> MBR -> Double
enlargement MBR
ba MBR
bl Double -> Double -> Double
forall a. Num a => a -> a -> a
- MBR -> MBR -> Double
enlargement MBR
ba MBR
br)

      !(# MBR
be, !a
e, !MBR
bu, !a
u, !MBR
bv, !a
v #) = if MBR -> Double
delta MBR
bx Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
>= MBR -> Double
delta MBR
by
                                          then if MBR -> Double
delta MBR
bx Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
>= MBR -> Double
delta MBR
bz
                                                 then (# MBR
bx, a
x, MBR
by, a
y, MBR
bz, a
z #)
                                                 else (# MBR
bz, a
z, MBR
bx, a
x, MBR
by, a
y #)

                                          else if MBR -> Double
delta MBR
by Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
>= MBR -> Double
delta MBR
bz
                                                 then (# MBR
by, a
y, MBR
bx, a
x, MBR
bz, a
z #)
                                                 else (# MBR
bz, a
z, MBR
bx, a
x, MBR
by, a
y #)

      lw :: Q1 a
lw = L2 a -> MBR -> a -> Q1 a
forall a. L2 a -> MBR -> a -> Q1 a
Q1L (MBR -> MBR -> a -> MBR -> a -> L2 a
forall a. MBR -> MBR -> a -> MBR -> a -> L2 a
L2 (MBR -> MBR -> MBR
unionMBR MBR
bl MBR
be) MBR
bl a
l MBR
be a
e) MBR
br a
r

      rw :: Q1 a
rw = MBR -> a -> L2 a -> Q1 a
forall a. MBR -> a -> L2 a -> Q1 a
Q1R MBR
bl a
l (MBR -> MBR -> a -> MBR -> a -> L2 a
forall a. MBR -> MBR -> a -> MBR -> a -> L2 a
L2 (MBR -> MBR -> MBR
unionMBR MBR
br MBR
be) MBR
br a
r MBR
be a
e)

      !q1 :: Q1 a
q1 = case MBR -> MBR -> Double
enlargement MBR
be MBR
bl Double -> Double -> Ordering
forall a. Ord a => a -> a -> Ordering
`compare` MBR -> MBR -> Double
enlargement MBR
be MBR
br of
              Ordering
GT -> Q1 a
rw
              Ordering
LT -> Q1 a
lw
              Ordering
EQ | MBR -> Double
areaMBR MBR
bl Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
< MBR -> Double
areaMBR MBR
br -> Q1 a
lw
                 | Bool
otherwise               -> Q1 a
rw

  in (# Q1 a
q1, MBR
bu, a
u, MBR
bv, a
v #)



distribute2 :: Q1 a -> MBR -> a -> MBR -> a -> (# Q2 a, MBR, a #)
distribute2 :: forall a. Q1 a -> MBR -> a -> MBR -> a -> (# Q2 a, MBR, a #)
distribute2 Q1 a
q MBR
bx a
x MBR
by a
y =
  let delta :: MBR -> MBR -> MBR -> Double
delta MBR
bl MBR
br MBR
bd = Double -> Double
forall a. Num a => a -> a
abs (MBR -> MBR -> Double
enlargement MBR
bd MBR
bl Double -> Double -> Double
forall a. Num a => a -> a -> a
- MBR -> MBR -> Double
enlargement MBR
bd MBR
br)
  in case Q1 a
q of
       Q1L l :: L2 a
l@(L2 MBR
bl MBR
ba a
a MBR
bb a
b) MBR
br a
r ->
         let !(# MBR
be, !a
e, !MBR
bz, !a
z #) | MBR -> MBR -> MBR -> Double
delta MBR
bl MBR
br MBR
bx Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
>= MBR -> MBR -> MBR -> Double
delta MBR
bl MBR
br MBR
by = (# MBR
bx, a
x, MBR
by, a
y #)
                                    | Bool
otherwise                        = (# MBR
by, a
y, MBR
bx, a
x #)

             lw :: Q2 a
lw = L3 a -> MBR -> a -> Q2 a
forall a. L3 a -> MBR -> a -> Q2 a
Q2L (MBR -> MBR -> a -> MBR -> a -> MBR -> a -> L3 a
forall a. MBR -> MBR -> a -> MBR -> a -> MBR -> a -> L3 a
L3 (MBR -> MBR -> MBR
unionMBR MBR
bl MBR
be) MBR
ba a
a MBR
bb a
b MBR
be a
e) MBR
br a
r

             rw :: Q2 a
rw = L2 a -> L2 a -> Q2 a
forall a. L2 a -> L2 a -> Q2 a
Q2M L2 a
l (MBR -> MBR -> a -> MBR -> a -> L2 a
forall a. MBR -> MBR -> a -> MBR -> a -> L2 a
L2 (MBR -> MBR -> MBR
unionMBR MBR
br MBR
be) MBR
br a
r MBR
be a
e)

             !q2 :: Q2 a
q2 = case MBR -> MBR -> Double
enlargement MBR
be MBR
bl Double -> Double -> Ordering
forall a. Ord a => a -> a -> Ordering
`compare` MBR -> MBR -> Double
enlargement MBR
be MBR
br of
                     Ordering
GT -> Q2 a
rw
                     Ordering
LT -> Q2 a
lw
                     Ordering
EQ | MBR -> Double
areaMBR MBR
bl Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
<= MBR -> Double
areaMBR MBR
br -> Q2 a
lw
                        | Bool
otherwise                -> Q2 a
rw

         in (# Q2 a
q2, MBR
bz, a
z #)

       Q1R MBR
bl a
l r :: L2 a
r@(L2 MBR
br MBR
ba a
a MBR
bb a
b) ->
         let !(# MBR
be, !a
e, !MBR
bz, !a
z #) | MBR -> MBR -> MBR -> Double
delta MBR
bl MBR
br MBR
bx Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
>= MBR -> MBR -> MBR -> Double
delta MBR
bl MBR
br MBR
by = (# MBR
bx, a
x, MBR
by, a
y #)
                                    | Bool
otherwise                        = (# MBR
by, a
y, MBR
bx, a
x #)

             lw :: Q2 a
lw = L2 a -> L2 a -> Q2 a
forall a. L2 a -> L2 a -> Q2 a
Q2M (MBR -> MBR -> a -> MBR -> a -> L2 a
forall a. MBR -> MBR -> a -> MBR -> a -> L2 a
L2 (MBR -> MBR -> MBR
unionMBR MBR
bl MBR
be) MBR
bl a
l MBR
be a
e) L2 a
r

             rw :: Q2 a
rw = MBR -> a -> L3 a -> Q2 a
forall a. MBR -> a -> L3 a -> Q2 a
Q2R MBR
bl a
l (MBR -> MBR -> a -> MBR -> a -> MBR -> a -> L3 a
forall a. MBR -> MBR -> a -> MBR -> a -> MBR -> a -> L3 a
L3 (MBR -> MBR -> MBR
unionMBR MBR
br MBR
be) MBR
ba a
a MBR
bb a
b MBR
be a
e)

             !q2 :: Q2 a
q2 = case MBR -> MBR -> Double
enlargement MBR
be MBR
bl Double -> Double -> Ordering
forall a. Ord a => a -> a -> Ordering
`compare` MBR -> MBR -> Double
enlargement MBR
be MBR
br of
                     Ordering
GT -> Q2 a
rw
                     Ordering
LT -> Q2 a
lw
                     Ordering
EQ | MBR -> Double
areaMBR MBR
bl Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
<= MBR -> Double
areaMBR MBR
br -> Q2 a
lw
                        | Bool
otherwise                -> Q2 a
rw

         in (# Q2 a
q2, MBR
bz, a
z #)


distribute1 :: Q2 a -> MBR -> a -> Q3 a
distribute1 :: forall a. Q2 a -> MBR -> a -> Q3 a
distribute1 Q2 a
q MBR
bx a
x =
  case Q2 a
q of
    Q2M l :: L2 a
l@(L2 MBR
bl MBR
ba a
a MBR
bb a
b) r :: L2 a
r@(L2 MBR
br MBR
bc a
c MBR
bd a
d) ->
      let lw :: Q3 a
lw = L3 a -> L2 a -> Q3 a
forall a. L3 a -> L2 a -> Q3 a
Q3L (MBR -> MBR -> a -> MBR -> a -> MBR -> a -> L3 a
forall a. MBR -> MBR -> a -> MBR -> a -> MBR -> a -> L3 a
L3 (MBR -> MBR -> MBR
unionMBR MBR
bl MBR
bx) MBR
ba a
a MBR
bb a
b MBR
bx a
x) L2 a
r

          rw :: Q3 a
rw = L2 a -> L3 a -> Q3 a
forall a. L2 a -> L3 a -> Q3 a
Q3R L2 a
l (MBR -> MBR -> a -> MBR -> a -> MBR -> a -> L3 a
forall a. MBR -> MBR -> a -> MBR -> a -> MBR -> a -> L3 a
L3 (MBR -> MBR -> MBR
unionMBR MBR
br MBR
bx) MBR
bc a
c MBR
bd a
d MBR
bx a
x)

      in case MBR -> MBR -> Double
enlargement MBR
bx MBR
bl Double -> Double -> Ordering
forall a. Ord a => a -> a -> Ordering
`compare` MBR -> MBR -> Double
enlargement MBR
bx MBR
br of
           Ordering
GT -> Q3 a
rw
           Ordering
LT -> Q3 a
lw
           Ordering
EQ | MBR -> Double
areaMBR MBR
bl Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
<= MBR -> Double
areaMBR MBR
br -> Q3 a
lw
              | Bool
otherwise                -> Q3 a
rw

    Q2L L3 a
l MBR
br a
r -> L3 a -> L2 a -> Q3 a
forall a. L3 a -> L2 a -> Q3 a
Q3L L3 a
l (MBR -> MBR -> a -> MBR -> a -> L2 a
forall a. MBR -> MBR -> a -> MBR -> a -> L2 a
L2 (MBR -> MBR -> MBR
unionMBR MBR
br MBR
bx) MBR
br a
r MBR
bx a
x)

    Q2R MBR
bl a
l L3 a
r -> L2 a -> L3 a -> Q3 a
forall a. L2 a -> L3 a -> Q3 a
Q3R (MBR -> MBR -> a -> MBR -> a -> L2 a
forall a. MBR -> MBR -> a -> MBR -> a -> L2 a
L2 (MBR -> MBR -> MBR
unionMBR MBR
bl MBR
bx) MBR
bl a
l MBR
bx a
x) L3 a
r



data Carry a = CarryLeaf MBR a
             | CarryNode Int MBR (R2Tree a)

data Ins a = InsOne MBR (R2Tree a)
           | InsCarry Word (Carry a) MBR (R2Tree a)
           | InsTwo Word MBR (R2Tree a) MBR (R2Tree a)

-- | \(\mathcal{O}(\log n)\). Insert a value into the tree.
--
--   'insert' uses the R*-tree insertion algorithm.
insert :: MBR -> a -> R2Tree a -> R2Tree a
insert :: forall a. MBR -> a -> R2Tree a -> R2Tree a
insert MBR
bx a
x R2Tree a
n =
  case R2Tree a
n of
    Node2 MBR
ba R2Tree a
a MBR
bb R2Tree a
b           ->
      let add :: (MBR -> R2Tree a -> Ins a)
-> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
add MBR -> R2Tree a -> Ins a
f MBR
bg R2Tree a
g MBR
bh R2Tree a
h =
            let !(# MBR
be, R2Tree a
e, !MBR
bz, !R2Tree a
z #) = MBR
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> (# MBR, R2Tree a, MBR, R2Tree a #)
forall a. MBR -> MBR -> a -> MBR -> a -> (# MBR, a, MBR, a #)
leastEnlargement2 MBR
bx MBR
bg R2Tree a
g MBR
bh R2Tree a
h
            in case MBR -> R2Tree a -> Ins a
f MBR
be R2Tree a
e of
                 InsOne MBR
bo R2Tree a
o              -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
forall a. MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node2 MBR
bo R2Tree a
o MBR
bz R2Tree a
z
                 InsCarry Word
mask Carry a
carry MBR
bo R2Tree a
o ->
                   case Carry a
carry of
                     CarryLeaf MBR
bu a
u       ->
                       (MBR -> R2Tree a -> Ins a)
-> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
add (Word -> MBR -> a -> Int -> MBR -> R2Tree a -> Ins a
forall a. Word -> MBR -> a -> Int -> MBR -> R2Tree a -> Ins a
insert_ Word
mask MBR
bu a
u Int
0) MBR
bo R2Tree a
o MBR
bz R2Tree a
z

                     CarryNode Int
depth MBR
bu R2Tree a
u ->
                       (MBR -> R2Tree a -> Ins a)
-> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
add (Word -> Int -> MBR -> R2Tree a -> Int -> MBR -> R2Tree a -> Ins a
forall a.
Word -> Int -> MBR -> R2Tree a -> Int -> MBR -> R2Tree a -> Ins a
insertNode Word
mask Int
depth MBR
bu R2Tree a
u Int
0) MBR
bo R2Tree a
o MBR
bz R2Tree a
z

                 InsTwo Word
_ MBR
bl R2Tree a
l MBR
br R2Tree a
r               -> MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
forall a.
MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node3 MBR
bl R2Tree a
l MBR
br R2Tree a
r MBR
bz R2Tree a
z

      in (MBR -> R2Tree a -> Ins a)
-> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
forall {a}.
(MBR -> R2Tree a -> Ins a)
-> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
add (Word -> MBR -> a -> Int -> MBR -> R2Tree a -> Ins a
forall a. Word -> MBR -> a -> Int -> MBR -> R2Tree a -> Ins a
insert_ Word
0 MBR
bx a
x Int
0) MBR
ba R2Tree a
a MBR
bb R2Tree a
b

    Node3 MBR
ba R2Tree a
a MBR
bb R2Tree a
b MBR
bc R2Tree a
c      ->
      let add :: (MBR -> R2Tree a -> Ins a)
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> R2Tree a
add MBR -> R2Tree a -> Ins a
f MBR
bg R2Tree a
g MBR
bh R2Tree a
h MBR
bi R2Tree a
i =
            let !(# MBR
be, R2Tree a
e, !MBR
by, !R2Tree a
y, !MBR
bz, !R2Tree a
z #) = MBR
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> (# MBR, R2Tree a, MBR, R2Tree a, MBR, R2Tree a #)
forall a.
MBR
-> MBR -> a -> MBR -> a -> MBR -> a -> (# MBR, a, MBR, a, MBR, a #)
leastEnlargement3 MBR
bx MBR
bg R2Tree a
g MBR
bh R2Tree a
h MBR
bi R2Tree a
i
            in case MBR -> R2Tree a -> Ins a
f MBR
be R2Tree a
e of
                 InsOne MBR
bo R2Tree a
o              -> MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
forall a.
MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node3 MBR
bo R2Tree a
o MBR
by R2Tree a
y MBR
bz R2Tree a
z
                 InsCarry Word
mask Carry a
carry MBR
bo R2Tree a
o ->
                   case Carry a
carry of
                     CarryLeaf MBR
bu a
u       ->
                       (MBR -> R2Tree a -> Ins a)
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> R2Tree a
add (Word -> MBR -> a -> Int -> MBR -> R2Tree a -> Ins a
forall a. Word -> MBR -> a -> Int -> MBR -> R2Tree a -> Ins a
insert_ Word
mask MBR
bu a
u Int
0) MBR
bo R2Tree a
o MBR
by R2Tree a
y MBR
bz R2Tree a
z

                     CarryNode Int
depth MBR
bu R2Tree a
u ->
                       (MBR -> R2Tree a -> Ins a)
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> R2Tree a
add (Word -> Int -> MBR -> R2Tree a -> Int -> MBR -> R2Tree a -> Ins a
forall a.
Word -> Int -> MBR -> R2Tree a -> Int -> MBR -> R2Tree a -> Ins a
insertNode Word
mask Int
depth MBR
bu R2Tree a
u Int
0) MBR
bo R2Tree a
o MBR
by R2Tree a
y MBR
bz R2Tree a
z

                 InsTwo Word
_ MBR
bl R2Tree a
l MBR
br R2Tree a
r               -> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> R2Tree a
forall a.
MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> R2Tree a
Node4 MBR
bl R2Tree a
l MBR
br R2Tree a
r MBR
by R2Tree a
y MBR
bz R2Tree a
z

      in (MBR -> R2Tree a -> Ins a)
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> R2Tree a
forall {a}.
(MBR -> R2Tree a -> Ins a)
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> R2Tree a
add (Word -> MBR -> a -> Int -> MBR -> R2Tree a -> Ins a
forall a. Word -> MBR -> a -> Int -> MBR -> R2Tree a -> Ins a
insert_ Word
0 MBR
bx a
x Int
0) MBR
ba R2Tree a
a MBR
bb R2Tree a
b MBR
bc R2Tree a
c

    Node4 MBR
ba R2Tree a
a MBR
bb R2Tree a
b MBR
bc R2Tree a
c MBR
bd R2Tree a
d ->
      let add :: (MBR -> R2Tree a -> Ins a)
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> R2Tree a
add MBR -> R2Tree a -> Ins a
f MBR
bg R2Tree a
g MBR
bh R2Tree a
h MBR
bi R2Tree a
i MBR
bj R2Tree a
j =
            let !(# MBR
be, R2Tree a
e, !MBR
bw, !R2Tree a
w, !MBR
by, !R2Tree a
y, !MBR
bz, !R2Tree a
z #) = MBR
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> (# MBR, R2Tree a, MBR, R2Tree a, MBR, R2Tree a, MBR, R2Tree a #)
forall a.
MBR
-> MBR
-> a
-> MBR
-> a
-> MBR
-> a
-> MBR
-> a
-> (# MBR, a, MBR, a, MBR, a, MBR, a #)
leastEnlargement4 MBR
bx MBR
bg R2Tree a
g MBR
bh R2Tree a
h MBR
bi R2Tree a
i MBR
bj R2Tree a
j
            in case MBR -> R2Tree a -> Ins a
f MBR
be R2Tree a
e of
                 InsOne MBR
bo R2Tree a
o              -> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> R2Tree a
forall a.
MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> R2Tree a
Node4 MBR
bo R2Tree a
o MBR
bw R2Tree a
w MBR
by R2Tree a
y MBR
bz R2Tree a
z
                 InsCarry Word
mask Carry a
carry MBR
bo R2Tree a
o ->
                   case Carry a
carry of
                     CarryLeaf MBR
bu a
u       ->
                       (MBR -> R2Tree a -> Ins a)
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> R2Tree a
add (Word -> MBR -> a -> Int -> MBR -> R2Tree a -> Ins a
forall a. Word -> MBR -> a -> Int -> MBR -> R2Tree a -> Ins a
insert_ Word
mask MBR
bu a
u Int
0) MBR
bo R2Tree a
o MBR
bw R2Tree a
w MBR
by R2Tree a
y MBR
bz R2Tree a
z

                     CarryNode Int
depth MBR
bu R2Tree a
u ->
                       (MBR -> R2Tree a -> Ins a)
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> R2Tree a
add (Word -> Int -> MBR -> R2Tree a -> Int -> MBR -> R2Tree a -> Ins a
forall a.
Word -> Int -> MBR -> R2Tree a -> Int -> MBR -> R2Tree a -> Ins a
insertNode Word
mask Int
depth MBR
bu R2Tree a
u Int
0) MBR
bo R2Tree a
o MBR
bw R2Tree a
w MBR
by R2Tree a
y MBR
bz R2Tree a
z

                 InsTwo Word
_ MBR
bl R2Tree a
l MBR
br R2Tree a
r               ->
                   case MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> Q3 (R2Tree a)
forall a.
MBR -> a -> MBR -> a -> MBR -> a -> MBR -> a -> MBR -> a -> Q3 a
sortSplit MBR
bl R2Tree a
l MBR
br R2Tree a
r MBR
bw R2Tree a
w MBR
by R2Tree a
y MBR
bz R2Tree a
z of
                     Q3L (L3 MBR
bl' MBR
bm R2Tree a
m MBR
bo R2Tree a
o MBR
bp R2Tree a
p) (L2 MBR
br' MBR
bs R2Tree a
s MBR
bt R2Tree a
t) ->
                       MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
forall a. MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node2 MBR
bl' (MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
forall a.
MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node3 MBR
bm R2Tree a
m MBR
bo R2Tree a
o MBR
bp R2Tree a
p) MBR
br' (MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
forall a. MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node2 MBR
bs R2Tree a
s MBR
bt R2Tree a
t)

                     Q3R (L2 MBR
bl' MBR
bm R2Tree a
m MBR
bo R2Tree a
o) (L3 MBR
br' MBR
bp R2Tree a
p MBR
bs R2Tree a
s MBR
bt R2Tree a
t) ->
                       MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
forall a. MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node2 MBR
bl' (MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
forall a. MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node2 MBR
bm R2Tree a
m MBR
bo R2Tree a
o) MBR
br' (MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
forall a.
MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node3 MBR
bp R2Tree a
p MBR
bs R2Tree a
s MBR
bt R2Tree a
t)

      in (MBR -> R2Tree a -> Ins a)
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> R2Tree a
forall {a}.
(MBR -> R2Tree a -> Ins a)
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> R2Tree a
add (Word -> MBR -> a -> Int -> MBR -> R2Tree a -> Ins a
forall a. Word -> MBR -> a -> Int -> MBR -> R2Tree a -> Ins a
insert_ Word
0 MBR
bx a
x Int
0) MBR
ba R2Tree a
a MBR
bb R2Tree a
b MBR
bc R2Tree a
c MBR
bd R2Tree a
d

    Leaf2 MBR
ba a
a MBR
bb a
b           -> MBR -> a -> MBR -> a -> MBR -> a -> R2Tree a
forall a. MBR -> a -> MBR -> a -> MBR -> a -> R2Tree a
Leaf3 MBR
ba a
a MBR
bb a
b MBR
bx a
x
    Leaf3 MBR
ba a
a MBR
bb a
b MBR
bc a
c      -> MBR -> a -> MBR -> a -> MBR -> a -> MBR -> a -> R2Tree a
forall a. MBR -> a -> MBR -> a -> MBR -> a -> MBR -> a -> R2Tree a
Leaf4 MBR
ba a
a MBR
bb a
b MBR
bc a
c MBR
bx a
x
    Leaf4 MBR
ba a
a MBR
bb a
b MBR
bc a
c MBR
bd a
d ->
      case MBR -> a -> MBR -> a -> MBR -> a -> MBR -> a -> MBR -> a -> Q3 a
forall a.
MBR -> a -> MBR -> a -> MBR -> a -> MBR -> a -> MBR -> a -> Q3 a
sortSplit MBR
ba a
a MBR
bb a
b MBR
bc a
c MBR
bd a
d MBR
bx a
x of
        Q3L (L3 MBR
bl MBR
bu a
u MBR
bv a
v MBR
bw a
w) (L2 MBR
br MBR
by a
y MBR
bz a
z) ->
          MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
forall a. MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node2 MBR
bl (MBR -> a -> MBR -> a -> MBR -> a -> R2Tree a
forall a. MBR -> a -> MBR -> a -> MBR -> a -> R2Tree a
Leaf3 MBR
bu a
u MBR
bv a
v MBR
bw a
w) MBR
br (MBR -> a -> MBR -> a -> R2Tree a
forall a. MBR -> a -> MBR -> a -> R2Tree a
Leaf2 MBR
by a
y MBR
bz a
z)

        Q3R (L2 MBR
bl MBR
bu a
u MBR
bv a
v) (L3 MBR
br MBR
bw a
w MBR
by a
y MBR
bz a
z) ->
          MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
forall a. MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node2 MBR
bl (MBR -> a -> MBR -> a -> R2Tree a
forall a. MBR -> a -> MBR -> a -> R2Tree a
Leaf2 MBR
bu a
u MBR
bv a
v) MBR
br (MBR -> a -> MBR -> a -> MBR -> a -> R2Tree a
forall a. MBR -> a -> MBR -> a -> MBR -> a -> R2Tree a
Leaf3 MBR
bw a
w MBR
by a
y MBR
bz a
z)

    Leaf1 MBR
ba a
a                -> MBR -> a -> MBR -> a -> R2Tree a
forall a. MBR -> a -> MBR -> a -> R2Tree a
Leaf2 MBR
ba a
a MBR
bx a
x
    R2Tree a
Empty                     -> MBR -> a -> R2Tree a
forall a. MBR -> a -> R2Tree a
Leaf1 MBR
bx a
x



insert_ :: Word -> MBR -> a -> Int -> MBR -> R2Tree a -> Ins a
insert_ :: forall a. Word -> MBR -> a -> Int -> MBR -> R2Tree a -> Ins a
insert_ Word
mask MBR
bx a
x = Int -> MBR -> R2Tree a -> Ins a
go
  where
    go :: Int -> MBR -> R2Tree a -> Ins a
go Int
height MBR
bn R2Tree a
n =
      case R2Tree a
n of
        Node2 MBR
ba R2Tree a
a MBR
bb R2Tree a
b           ->
          let !(# MBR
be, R2Tree a
e, !MBR
bz, !R2Tree a
z #) = MBR
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> (# MBR, R2Tree a, MBR, R2Tree a #)
forall a. MBR -> MBR -> a -> MBR -> a -> (# MBR, a, MBR, a #)
leastEnlargement2 MBR
bx MBR
ba R2Tree a
a MBR
bb R2Tree a
b
          in case Int -> MBR -> R2Tree a -> Ins a
go (Int
height Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) MBR
be R2Tree a
e of
               InsOne MBR
bo R2Tree a
o               -> MBR -> R2Tree a -> Ins a
forall a. MBR -> R2Tree a -> Ins a
InsOne (MBR -> MBR -> MBR
unionMBR MBR
bo MBR
bz) (MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
forall a. MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node2 MBR
bo R2Tree a
o MBR
bz R2Tree a
z)
               InsCarry Word
mask' Carry a
carry MBR
bo R2Tree a
o ->
                 Word -> Carry a -> MBR -> R2Tree a -> Ins a
forall a. Word -> Carry a -> MBR -> R2Tree a -> Ins a
InsCarry Word
mask' Carry a
carry (MBR -> MBR -> MBR
unionMBR MBR
bo MBR
bz) (MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
forall a. MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node2 MBR
bo R2Tree a
o MBR
bz R2Tree a
z)

               InsTwo Word
_ MBR
bl R2Tree a
l MBR
br R2Tree a
r        ->
                 MBR -> R2Tree a -> Ins a
forall a. MBR -> R2Tree a -> Ins a
InsOne (MBR -> MBR -> MBR -> MBR
union3MBR MBR
bl MBR
br MBR
bz) (MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
forall a.
MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node3 MBR
bl R2Tree a
l MBR
br R2Tree a
r MBR
bz R2Tree a
z)

        Node3 MBR
ba R2Tree a
a MBR
bb R2Tree a
b MBR
bc R2Tree a
c      ->
          let !(# MBR
be, R2Tree a
e, !MBR
by, !R2Tree a
y, !MBR
bz, !R2Tree a
z #) = MBR
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> (# MBR, R2Tree a, MBR, R2Tree a, MBR, R2Tree a #)
forall a.
MBR
-> MBR -> a -> MBR -> a -> MBR -> a -> (# MBR, a, MBR, a, MBR, a #)
leastEnlargement3 MBR
bx MBR
ba R2Tree a
a MBR
bb R2Tree a
b MBR
bc R2Tree a
c
          in case Int -> MBR -> R2Tree a -> Ins a
go (Int
height Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) MBR
be R2Tree a
e of
               InsOne MBR
bo R2Tree a
o               ->
                 MBR -> R2Tree a -> Ins a
forall a. MBR -> R2Tree a -> Ins a
InsOne (MBR -> MBR -> MBR -> MBR
union3MBR MBR
bo MBR
by MBR
bz) (MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
forall a.
MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node3 MBR
bo R2Tree a
o MBR
by R2Tree a
y MBR
bz R2Tree a
z)

               InsCarry Word
mask' Carry a
carry MBR
bo R2Tree a
o ->
                 Word -> Carry a -> MBR -> R2Tree a -> Ins a
forall a. Word -> Carry a -> MBR -> R2Tree a -> Ins a
InsCarry Word
mask' Carry a
carry (MBR -> MBR -> MBR -> MBR
union3MBR MBR
bo MBR
by MBR
bz) (MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
forall a.
MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node3 MBR
bo R2Tree a
o MBR
by R2Tree a
y MBR
bz R2Tree a
z)

               InsTwo Word
_ MBR
bl R2Tree a
l MBR
br R2Tree a
r        ->
                 MBR -> R2Tree a -> Ins a
forall a. MBR -> R2Tree a -> Ins a
InsOne (MBR -> MBR -> MBR -> MBR -> MBR
union4MBR MBR
bl MBR
br MBR
by MBR
bz) (MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> R2Tree a
forall a.
MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> R2Tree a
Node4 MBR
bl R2Tree a
l MBR
br R2Tree a
r MBR
by R2Tree a
y MBR
bz R2Tree a
z)

        Node4 MBR
ba R2Tree a
a MBR
bb R2Tree a
b MBR
bc R2Tree a
c MBR
bd R2Tree a
d ->
          let !(# MBR
be, R2Tree a
e, !MBR
bw, !R2Tree a
w, !MBR
by, !R2Tree a
y, !MBR
bz, !R2Tree a
z #) = MBR
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> (# MBR, R2Tree a, MBR, R2Tree a, MBR, R2Tree a, MBR, R2Tree a #)
forall a.
MBR
-> MBR
-> a
-> MBR
-> a
-> MBR
-> a
-> MBR
-> a
-> (# MBR, a, MBR, a, MBR, a, MBR, a #)
leastEnlargement4 MBR
bx MBR
ba R2Tree a
a MBR
bb R2Tree a
b MBR
bc R2Tree a
c MBR
bd R2Tree a
d
          in case Int -> MBR -> R2Tree a -> Ins a
go (Int
height Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) MBR
be R2Tree a
e of
               InsOne MBR
bo R2Tree a
o               ->
                 MBR -> R2Tree a -> Ins a
forall a. MBR -> R2Tree a -> Ins a
InsOne (MBR -> MBR -> MBR -> MBR -> MBR
union4MBR MBR
bo MBR
bw MBR
by MBR
bz) (MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> R2Tree a
forall a.
MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> R2Tree a
Node4 MBR
bo R2Tree a
o MBR
bw R2Tree a
w MBR
by R2Tree a
y MBR
bz R2Tree a
z)

               InsCarry Word
mask' Carry a
carry MBR
bo R2Tree a
o ->
                 Word -> Carry a -> MBR -> R2Tree a -> Ins a
forall a. Word -> Carry a -> MBR -> R2Tree a -> Ins a
InsCarry Word
mask' Carry a
carry (MBR -> MBR -> MBR -> MBR -> MBR
union4MBR MBR
bo MBR
bw MBR
by MBR
bz) (MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> R2Tree a
forall a.
MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> R2Tree a
Node4 MBR
bo R2Tree a
o MBR
bw R2Tree a
w MBR
by R2Tree a
y MBR
bz R2Tree a
z)

               InsTwo Word
_ MBR
bl R2Tree a
l MBR
br R2Tree a
r        ->
                 let bit_ :: Word
bit_ = Word
1 Word -> Int -> Word
forall a. Bits a => a -> Int -> a
`unsafeShiftL` Int
height
                 in case Word
mask Word -> Word -> Word
forall a. Bits a => a -> a -> a
.&. Word
bit_ of
                      Word
0 ->
                        case MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> Q3 (R2Tree a)
forall a.
MBR -> a -> MBR -> a -> MBR -> a -> MBR -> a -> MBR -> a -> Q3 a
sortSplit MBR
bl R2Tree a
l MBR
br R2Tree a
r MBR
bw R2Tree a
w MBR
by R2Tree a
y MBR
bz R2Tree a
z of
                          Q3L (L3 MBR
bl' MBR
bm R2Tree a
m MBR
bo R2Tree a
o MBR
bp R2Tree a
p) (L2 MBR
br' MBR
bs R2Tree a
s MBR
bt R2Tree a
t) ->
                            Word -> MBR -> R2Tree a -> MBR -> R2Tree a -> Ins a
forall a. Word -> MBR -> R2Tree a -> MBR -> R2Tree a -> Ins a
InsTwo Word
mask MBR
bl' (MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
forall a.
MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node3 MBR
bm R2Tree a
m MBR
bo R2Tree a
o MBR
bp R2Tree a
p) MBR
br' (MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
forall a. MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node2 MBR
bs R2Tree a
s MBR
bt R2Tree a
t)

                          Q3R (L2 MBR
bl' MBR
bm R2Tree a
m MBR
bo R2Tree a
o) (L3 MBR
br' MBR
bp R2Tree a
p MBR
bs R2Tree a
s MBR
bt R2Tree a
t) ->
                            Word -> MBR -> R2Tree a -> MBR -> R2Tree a -> Ins a
forall a. Word -> MBR -> R2Tree a -> MBR -> R2Tree a -> Ins a
InsTwo Word
mask MBR
bl' (MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
forall a. MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node2 MBR
bm R2Tree a
m MBR
bo R2Tree a
o) MBR
br' (MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
forall a.
MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node3 MBR
bp R2Tree a
p MBR
bs R2Tree a
s MBR
bt R2Tree a
t)

                      Word
_ ->
                        let !(# MBR
bm, R2Tree a
m, MBR
bo, R2Tree a
o, MBR
bp, R2Tree a
p, MBR
bs, R2Tree a
s, MBR
bt, R2Tree a
t #) =
                               MBR
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> (# MBR, R2Tree a, MBR, R2Tree a, MBR, R2Tree a, MBR, R2Tree a,
      MBR, R2Tree a #)
forall a.
MBR
-> MBR
-> a
-> MBR
-> a
-> MBR
-> a
-> MBR
-> a
-> MBR
-> a
-> (# MBR, a, MBR, a, MBR, a, MBR, a, MBR, a #)
sort5Distance (MBR -> MBR -> MBR
unionMBR MBR
bn MBR
bx) MBR
bl R2Tree a
l MBR
br R2Tree a
r MBR
bw R2Tree a
w MBR
by R2Tree a
y MBR
bz R2Tree a
z

                        in Word -> Carry a -> MBR -> R2Tree a -> Ins a
forall a. Word -> Carry a -> MBR -> R2Tree a -> Ins a
InsCarry (Word
mask Word -> Word -> Word
forall a. Bits a => a -> a -> a
.|. Word
bit_) (Int -> MBR -> R2Tree a -> Carry a
forall a. Int -> MBR -> R2Tree a -> Carry a
CarryNode Int
height MBR
bt R2Tree a
t)
                             (MBR -> MBR -> MBR -> MBR -> MBR
union4MBR MBR
bm MBR
bo MBR
bp MBR
bs) (MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> R2Tree a
forall a.
MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> R2Tree a
Node4 MBR
bm R2Tree a
m MBR
bo R2Tree a
o MBR
bp R2Tree a
p MBR
bs R2Tree a
s)

        Leaf2 MBR
ba a
a MBR
bb a
b           ->
          MBR -> R2Tree a -> Ins a
forall a. MBR -> R2Tree a -> Ins a
InsOne (MBR -> MBR -> MBR -> MBR
union3MBR MBR
ba MBR
bb MBR
bx) (MBR -> a -> MBR -> a -> MBR -> a -> R2Tree a
forall a. MBR -> a -> MBR -> a -> MBR -> a -> R2Tree a
Leaf3 MBR
ba a
a MBR
bb a
b MBR
bx a
x)

        Leaf3 MBR
ba a
a MBR
bb a
b MBR
bc a
c      ->
          MBR -> R2Tree a -> Ins a
forall a. MBR -> R2Tree a -> Ins a
InsOne (MBR -> MBR -> MBR -> MBR -> MBR
union4MBR MBR
ba MBR
bb MBR
bc MBR
bx) (MBR -> a -> MBR -> a -> MBR -> a -> MBR -> a -> R2Tree a
forall a. MBR -> a -> MBR -> a -> MBR -> a -> MBR -> a -> R2Tree a
Leaf4 MBR
ba a
a MBR
bb a
b MBR
bc a
c MBR
bx a
x)

        Leaf4 MBR
ba a
a MBR
bb a
b MBR
bc a
c MBR
bd a
d ->
          let bit_ :: Word
bit_ = Word
1 Word -> Int -> Word
forall a. Bits a => a -> Int -> a
`unsafeShiftL` Int
height
          in case Word
mask Word -> Word -> Word
forall a. Bits a => a -> a -> a
.&. Word
bit_ of
               Word
0 ->
                 case MBR -> a -> MBR -> a -> MBR -> a -> MBR -> a -> MBR -> a -> Q3 a
forall a.
MBR -> a -> MBR -> a -> MBR -> a -> MBR -> a -> MBR -> a -> Q3 a
sortSplit MBR
ba a
a MBR
bb a
b MBR
bc a
c MBR
bd a
d MBR
bx a
x of
                   Q3L (L3 MBR
bl MBR
bu a
u MBR
bv a
v MBR
bw a
w) (L2 MBR
br MBR
by a
y MBR
bz a
z) ->
                     Word -> MBR -> R2Tree a -> MBR -> R2Tree a -> Ins a
forall a. Word -> MBR -> R2Tree a -> MBR -> R2Tree a -> Ins a
InsTwo Word
mask MBR
bl (MBR -> a -> MBR -> a -> MBR -> a -> R2Tree a
forall a. MBR -> a -> MBR -> a -> MBR -> a -> R2Tree a
Leaf3 MBR
bu a
u MBR
bv a
v MBR
bw a
w) MBR
br (MBR -> a -> MBR -> a -> R2Tree a
forall a. MBR -> a -> MBR -> a -> R2Tree a
Leaf2 MBR
by a
y MBR
bz a
z)

                   Q3R (L2 MBR
bl MBR
bu a
u MBR
bv a
v) (L3 MBR
br MBR
bw a
w MBR
by a
y MBR
bz a
z) ->
                     Word -> MBR -> R2Tree a -> MBR -> R2Tree a -> Ins a
forall a. Word -> MBR -> R2Tree a -> MBR -> R2Tree a -> Ins a
InsTwo Word
mask MBR
bl (MBR -> a -> MBR -> a -> R2Tree a
forall a. MBR -> a -> MBR -> a -> R2Tree a
Leaf2 MBR
bu a
u MBR
bv a
v) MBR
br (MBR -> a -> MBR -> a -> MBR -> a -> R2Tree a
forall a. MBR -> a -> MBR -> a -> MBR -> a -> R2Tree a
Leaf3 MBR
bw a
w MBR
by a
y MBR
bz a
z)

               Word
_ ->
                 let !(# MBR
bu, a
u, MBR
bv, a
v, MBR
bw, a
w, MBR
by, a
y, MBR
bz, a
z #) =
                        MBR
-> MBR
-> a
-> MBR
-> a
-> MBR
-> a
-> MBR
-> a
-> MBR
-> a
-> (# MBR, a, MBR, a, MBR, a, MBR, a, MBR, a #)
forall a.
MBR
-> MBR
-> a
-> MBR
-> a
-> MBR
-> a
-> MBR
-> a
-> MBR
-> a
-> (# MBR, a, MBR, a, MBR, a, MBR, a, MBR, a #)
sort5Distance (MBR -> MBR -> MBR
unionMBR MBR
bn MBR
bx) MBR
ba a
a MBR
bb a
b MBR
bc a
c MBR
bd a
d MBR
bx a
x

                 in Word -> Carry a -> MBR -> R2Tree a -> Ins a
forall a. Word -> Carry a -> MBR -> R2Tree a -> Ins a
InsCarry (Word
mask Word -> Word -> Word
forall a. Bits a => a -> a -> a
.|. Word
bit_) (MBR -> a -> Carry a
forall a. MBR -> a -> Carry a
CarryLeaf MBR
bz a
z)
                      (MBR -> MBR -> MBR -> MBR -> MBR
union4MBR MBR
bu MBR
bv MBR
bw MBR
by) (MBR -> a -> MBR -> a -> MBR -> a -> MBR -> a -> R2Tree a
forall a. MBR -> a -> MBR -> a -> MBR -> a -> MBR -> a -> R2Tree a
Leaf4 MBR
bu a
u MBR
bv a
v MBR
bw a
w MBR
by a
y)

        Leaf1 MBR
ba a
a               ->
          MBR -> R2Tree a -> Ins a
forall a. MBR -> R2Tree a -> Ins a
InsOne (MBR -> MBR -> MBR
unionMBR MBR
ba MBR
bx) (MBR -> a -> MBR -> a -> R2Tree a
forall a. MBR -> a -> MBR -> a -> R2Tree a
Leaf2 MBR
ba a
a MBR
bx a
x)

        R2Tree a
Empty                    ->
          MBR -> R2Tree a -> Ins a
forall a. MBR -> R2Tree a -> Ins a
InsOne MBR
bx (MBR -> a -> R2Tree a
forall a. MBR -> a -> R2Tree a
Leaf1 MBR
bx a
x)


insertNode :: Word -> Int -> MBR -> R2Tree a -> Int -> MBR -> R2Tree a -> Ins a
insertNode :: forall a.
Word -> Int -> MBR -> R2Tree a -> Int -> MBR -> R2Tree a -> Ins a
insertNode Word
mask Int
depth MBR
bx R2Tree a
x = Int -> MBR -> R2Tree a -> Ins a
go
  where
    go :: Int -> MBR -> R2Tree a -> Ins a
go Int
height MBR
bn R2Tree a
n =
      case R2Tree a
n of
        Node2 MBR
ba R2Tree a
a MBR
bb R2Tree a
b
          | Int
height Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
depth ->
              let !(# MBR
be, R2Tree a
e, !MBR
bz, !R2Tree a
z #) = MBR
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> (# MBR, R2Tree a, MBR, R2Tree a #)
forall a. MBR -> MBR -> a -> MBR -> a -> (# MBR, a, MBR, a #)
leastEnlargement2 MBR
bx MBR
ba R2Tree a
a MBR
bb R2Tree a
b
              in case Int -> MBR -> R2Tree a -> Ins a
go (Int
height Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) MBR
be R2Tree a
e of
                   InsOne MBR
bo R2Tree a
o               -> MBR -> R2Tree a -> Ins a
forall a. MBR -> R2Tree a -> Ins a
InsOne (MBR -> MBR -> MBR
unionMBR MBR
bo MBR
bz) (MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
forall a. MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node2 MBR
bo R2Tree a
o MBR
bz R2Tree a
z)
                   InsCarry Word
mask' Carry a
carry MBR
bo R2Tree a
o ->
                     Word -> Carry a -> MBR -> R2Tree a -> Ins a
forall a. Word -> Carry a -> MBR -> R2Tree a -> Ins a
InsCarry Word
mask' Carry a
carry (MBR -> MBR -> MBR
unionMBR MBR
bo MBR
bz) (MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
forall a. MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node2 MBR
bo R2Tree a
o MBR
bz R2Tree a
z)

                   InsTwo Word
_ MBR
bl R2Tree a
l MBR
br R2Tree a
r        ->
                     MBR -> R2Tree a -> Ins a
forall a. MBR -> R2Tree a -> Ins a
InsOne (MBR -> MBR -> MBR -> MBR
union3MBR MBR
bl MBR
br MBR
bz) (MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
forall a.
MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node3 MBR
bl R2Tree a
l MBR
br R2Tree a
r MBR
bz R2Tree a
z)

          | Bool
otherwise       ->
              MBR -> R2Tree a -> Ins a
forall a. MBR -> R2Tree a -> Ins a
InsOne (MBR -> MBR -> MBR
unionMBR MBR
bn MBR
bx) (MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
forall a.
MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node3 MBR
ba R2Tree a
a MBR
bb R2Tree a
b MBR
bx R2Tree a
x)

        Node3 MBR
ba R2Tree a
a MBR
bb R2Tree a
b MBR
bc R2Tree a
c
          | Int
height Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
depth ->
              let !(# MBR
be, R2Tree a
e, !MBR
by, !R2Tree a
y, !MBR
bz, !R2Tree a
z #) = MBR
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> (# MBR, R2Tree a, MBR, R2Tree a, MBR, R2Tree a #)
forall a.
MBR
-> MBR -> a -> MBR -> a -> MBR -> a -> (# MBR, a, MBR, a, MBR, a #)
leastEnlargement3 MBR
bx MBR
ba R2Tree a
a MBR
bb R2Tree a
b MBR
bc R2Tree a
c
              in case Int -> MBR -> R2Tree a -> Ins a
go (Int
height Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) MBR
be R2Tree a
e of
                   InsOne MBR
bo R2Tree a
o               ->
                     MBR -> R2Tree a -> Ins a
forall a. MBR -> R2Tree a -> Ins a
InsOne (MBR -> MBR -> MBR -> MBR
union3MBR MBR
bo MBR
by MBR
bz) (MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
forall a.
MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node3 MBR
bo R2Tree a
o MBR
by R2Tree a
y MBR
bz R2Tree a
z)

                   InsCarry Word
mask' Carry a
carry MBR
bo R2Tree a
o ->
                     Word -> Carry a -> MBR -> R2Tree a -> Ins a
forall a. Word -> Carry a -> MBR -> R2Tree a -> Ins a
InsCarry Word
mask' Carry a
carry (MBR -> MBR -> MBR -> MBR
union3MBR MBR
bo MBR
by MBR
bz) (MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
forall a.
MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node3 MBR
bo R2Tree a
o MBR
by R2Tree a
y MBR
bz R2Tree a
z)

                   InsTwo Word
_ MBR
bl R2Tree a
l MBR
br R2Tree a
r        ->
                     MBR -> R2Tree a -> Ins a
forall a. MBR -> R2Tree a -> Ins a
InsOne (MBR -> MBR -> MBR -> MBR -> MBR
union4MBR MBR
bl MBR
br MBR
by MBR
bz) (MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> R2Tree a
forall a.
MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> R2Tree a
Node4 MBR
bl R2Tree a
l MBR
br R2Tree a
r MBR
by R2Tree a
y MBR
bz R2Tree a
z)

          | Bool
otherwise       ->
              MBR -> R2Tree a -> Ins a
forall a. MBR -> R2Tree a -> Ins a
InsOne (MBR -> MBR -> MBR
unionMBR MBR
bn MBR
bx) (MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> R2Tree a
forall a.
MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> R2Tree a
Node4 MBR
ba R2Tree a
a MBR
bb R2Tree a
b MBR
bc R2Tree a
c MBR
bx R2Tree a
x)

        Node4 MBR
ba R2Tree a
a MBR
bb R2Tree a
b MBR
bc R2Tree a
c MBR
bd R2Tree a
d
          | Int
height Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
depth ->
              let !(# MBR
be, R2Tree a
e, !MBR
bw, !R2Tree a
w, !MBR
by, !R2Tree a
y, !MBR
bz, !R2Tree a
z #) = MBR
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> (# MBR, R2Tree a, MBR, R2Tree a, MBR, R2Tree a, MBR, R2Tree a #)
forall a.
MBR
-> MBR
-> a
-> MBR
-> a
-> MBR
-> a
-> MBR
-> a
-> (# MBR, a, MBR, a, MBR, a, MBR, a #)
leastEnlargement4 MBR
bx MBR
ba R2Tree a
a MBR
bb R2Tree a
b MBR
bc R2Tree a
c MBR
bd R2Tree a
d
              in case Int -> MBR -> R2Tree a -> Ins a
go (Int
height Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) MBR
be R2Tree a
e of
                   InsOne MBR
bo R2Tree a
o               ->
                     MBR -> R2Tree a -> Ins a
forall a. MBR -> R2Tree a -> Ins a
InsOne (MBR -> MBR -> MBR -> MBR -> MBR
union4MBR MBR
bo MBR
bw MBR
by MBR
bz) (MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> R2Tree a
forall a.
MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> R2Tree a
Node4 MBR
bo R2Tree a
o MBR
bw R2Tree a
w MBR
by R2Tree a
y MBR
bz R2Tree a
z)

                   InsCarry Word
mask' Carry a
carry MBR
bo R2Tree a
o ->
                     Word -> Carry a -> MBR -> R2Tree a -> Ins a
forall a. Word -> Carry a -> MBR -> R2Tree a -> Ins a
InsCarry Word
mask' Carry a
carry (MBR -> MBR -> MBR -> MBR -> MBR
union4MBR MBR
bo MBR
bw MBR
by MBR
bz) (MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> R2Tree a
forall a.
MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> R2Tree a
Node4 MBR
bo R2Tree a
o MBR
bw R2Tree a
w MBR
by R2Tree a
y MBR
bz R2Tree a
z)

                   InsTwo Word
_ MBR
bl R2Tree a
l MBR
br R2Tree a
r        ->
                     let bit_ :: Word
bit_ = Word
1 Word -> Int -> Word
forall a. Bits a => a -> Int -> a
`unsafeShiftL` Int
height
                     in case Word
mask Word -> Word -> Word
forall a. Bits a => a -> a -> a
.&. Word
bit_ of
                          Word
0 ->
                            case MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> Q3 (R2Tree a)
forall a.
MBR -> a -> MBR -> a -> MBR -> a -> MBR -> a -> MBR -> a -> Q3 a
sortSplit MBR
bl R2Tree a
l MBR
br R2Tree a
r MBR
bw R2Tree a
w MBR
by R2Tree a
y MBR
bz R2Tree a
z of
                              Q3L (L3 MBR
bl' MBR
bm R2Tree a
m MBR
bo R2Tree a
o MBR
bp R2Tree a
p) (L2 MBR
br' MBR
bs R2Tree a
s MBR
bt R2Tree a
t) ->
                                Word -> MBR -> R2Tree a -> MBR -> R2Tree a -> Ins a
forall a. Word -> MBR -> R2Tree a -> MBR -> R2Tree a -> Ins a
InsTwo Word
mask MBR
bl' (MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
forall a.
MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node3 MBR
bm R2Tree a
m MBR
bo R2Tree a
o MBR
bp R2Tree a
p) MBR
br' (MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
forall a. MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node2 MBR
bs R2Tree a
s MBR
bt R2Tree a
t)

                              Q3R (L2 MBR
bl' MBR
bm R2Tree a
m MBR
bo R2Tree a
o) (L3 MBR
br' MBR
bp R2Tree a
p MBR
bs R2Tree a
s MBR
bt R2Tree a
t) ->
                                Word -> MBR -> R2Tree a -> MBR -> R2Tree a -> Ins a
forall a. Word -> MBR -> R2Tree a -> MBR -> R2Tree a -> Ins a
InsTwo Word
mask MBR
bl' (MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
forall a. MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node2 MBR
bm R2Tree a
m MBR
bo R2Tree a
o) MBR
br' (MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
forall a.
MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node3 MBR
bp R2Tree a
p MBR
bs R2Tree a
s MBR
bt R2Tree a
t)

                          Word
_ ->
                            let !(# MBR
bm, R2Tree a
m, MBR
bo, R2Tree a
o, MBR
bp, R2Tree a
p, MBR
bs, R2Tree a
s, MBR
bt, R2Tree a
t #) =
                                  MBR
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> (# MBR, R2Tree a, MBR, R2Tree a, MBR, R2Tree a, MBR, R2Tree a,
      MBR, R2Tree a #)
forall a.
MBR
-> MBR
-> a
-> MBR
-> a
-> MBR
-> a
-> MBR
-> a
-> MBR
-> a
-> (# MBR, a, MBR, a, MBR, a, MBR, a, MBR, a #)
sort5Distance (MBR -> MBR -> MBR
unionMBR MBR
bn MBR
bx) MBR
bl R2Tree a
l MBR
br R2Tree a
r MBR
bw R2Tree a
w MBR
by R2Tree a
y MBR
bz R2Tree a
z

                            in Word -> Carry a -> MBR -> R2Tree a -> Ins a
forall a. Word -> Carry a -> MBR -> R2Tree a -> Ins a
InsCarry (Word
mask Word -> Word -> Word
forall a. Bits a => a -> a -> a
.|. Word
bit_) (Int -> MBR -> R2Tree a -> Carry a
forall a. Int -> MBR -> R2Tree a -> Carry a
CarryNode Int
height MBR
bt R2Tree a
t)
                                 (MBR -> MBR -> MBR -> MBR -> MBR
union4MBR MBR
bm MBR
bo MBR
bp MBR
bs) (MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> R2Tree a
forall a.
MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> R2Tree a
Node4 MBR
bm R2Tree a
m MBR
bo R2Tree a
o MBR
bp R2Tree a
p MBR
bs R2Tree a
s)

          | Bool
otherwise       ->
              let bit_ :: Word
bit_ = Word
1 Word -> Int -> Word
forall a. Bits a => a -> Int -> a
`unsafeShiftL` Int
height
              in case Word
mask Word -> Word -> Word
forall a. Bits a => a -> a -> a
.&. Word
bit_ of
                   Word
0 ->
                     case MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> Q3 (R2Tree a)
forall a.
MBR -> a -> MBR -> a -> MBR -> a -> MBR -> a -> MBR -> a -> Q3 a
sortSplit MBR
ba R2Tree a
a MBR
bb R2Tree a
b MBR
bc R2Tree a
c MBR
bd R2Tree a
d MBR
bx R2Tree a
x of
                       Q3L (L3 MBR
bl' MBR
bm R2Tree a
m MBR
bo R2Tree a
o MBR
bp R2Tree a
p) (L2 MBR
br' MBR
bs R2Tree a
s MBR
bt R2Tree a
t) ->
                         Word -> MBR -> R2Tree a -> MBR -> R2Tree a -> Ins a
forall a. Word -> MBR -> R2Tree a -> MBR -> R2Tree a -> Ins a
InsTwo Word
mask MBR
bl' (MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
forall a.
MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node3 MBR
bm R2Tree a
m MBR
bo R2Tree a
o MBR
bp R2Tree a
p) MBR
br' (MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
forall a. MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node2 MBR
bs R2Tree a
s MBR
bt R2Tree a
t)

                       Q3R (L2 MBR
bl' MBR
bm R2Tree a
m MBR
bo R2Tree a
o) (L3 MBR
br' MBR
bp R2Tree a
p MBR
bs R2Tree a
s MBR
bt R2Tree a
t) ->
                         Word -> MBR -> R2Tree a -> MBR -> R2Tree a -> Ins a
forall a. Word -> MBR -> R2Tree a -> MBR -> R2Tree a -> Ins a
InsTwo Word
mask MBR
bl' (MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
forall a. MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node2 MBR
bm R2Tree a
m MBR
bo R2Tree a
o) MBR
br' (MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
forall a.
MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node3 MBR
bp R2Tree a
p MBR
bs R2Tree a
s MBR
bt R2Tree a
t)

                   Word
_ ->
                     let !(# MBR
bm, R2Tree a
m, MBR
bo, R2Tree a
o, MBR
bp, R2Tree a
p, MBR
bs, R2Tree a
s, MBR
bt, R2Tree a
t #) =
                           MBR
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> (# MBR, R2Tree a, MBR, R2Tree a, MBR, R2Tree a, MBR, R2Tree a,
      MBR, R2Tree a #)
forall a.
MBR
-> MBR
-> a
-> MBR
-> a
-> MBR
-> a
-> MBR
-> a
-> MBR
-> a
-> (# MBR, a, MBR, a, MBR, a, MBR, a, MBR, a #)
sort5Distance (MBR -> MBR -> MBR
unionMBR MBR
bn MBR
bx) MBR
ba R2Tree a
a MBR
bb R2Tree a
b MBR
bc R2Tree a
c MBR
bd R2Tree a
d MBR
bx R2Tree a
x

                     in Word -> Carry a -> MBR -> R2Tree a -> Ins a
forall a. Word -> Carry a -> MBR -> R2Tree a -> Ins a
InsCarry (Word
mask Word -> Word -> Word
forall a. Bits a => a -> a -> a
.|. Word
bit_) (Int -> MBR -> R2Tree a -> Carry a
forall a. Int -> MBR -> R2Tree a -> Carry a
CarryNode Int
height MBR
bt R2Tree a
t)
                          (MBR -> MBR -> MBR -> MBR -> MBR
union4MBR MBR
bm MBR
bo MBR
bp MBR
bs) (MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> R2Tree a
forall a.
MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> R2Tree a
Node4 MBR
bm R2Tree a
m MBR
bo R2Tree a
o MBR
bp R2Tree a
p MBR
bs R2Tree a
s)



        R2Tree a
_ -> String -> Ins a
forall a. String -> a
errorWithoutStackTrace String
"Data.R2Tree.Double.Internal.insertNode: reached a leaf"



sortSplit :: MBR -> a -> MBR -> a -> MBR -> a -> MBR -> a -> MBR -> a -> Q3 a
sortSplit :: forall a.
MBR -> a -> MBR -> a -> MBR -> a -> MBR -> a -> MBR -> a -> Q3 a
sortSplit MBR
ba a
a MBR
bb a
b MBR
bc a
c MBR
bd a
d MBR
be a
e =
  let v :: (# MBR, a, MBR, a, MBR, a, MBR, a, MBR, a #)
v = (MBR -> MBR -> Bool)
-> MBR
-> a
-> MBR
-> a
-> MBR
-> a
-> MBR
-> a
-> MBR
-> a
-> (# MBR, a, MBR, a, MBR, a, MBR, a, MBR, a #)
forall k a.
(k -> k -> Bool)
-> k
-> a
-> k
-> a
-> k
-> a
-> k
-> a
-> k
-> a
-> (# k, a, k, a, k, a, k, a, k, a #)
sort5_ MBR -> MBR -> Bool
vertical   MBR
ba a
a MBR
bb a
b MBR
bc a
c MBR
bd a
d MBR
be a
e
      h :: (# MBR, a, MBR, a, MBR, a, MBR, a, MBR, a #)
h = (MBR -> MBR -> Bool)
-> MBR
-> a
-> MBR
-> a
-> MBR
-> a
-> MBR
-> a
-> MBR
-> a
-> (# MBR, a, MBR, a, MBR, a, MBR, a, MBR, a #)
forall k a.
(k -> k -> Bool)
-> k
-> a
-> k
-> a
-> k
-> a
-> k
-> a
-> k
-> a
-> (# k, a, k, a, k, a, k, a, k, a #)
sort5_ MBR -> MBR -> Bool
horizontal MBR
ba a
a MBR
bb a
b MBR
bc a
c MBR
bd a
d MBR
be a
e

      vg :: (# L3 a, L2 a, L2 a, L3 a #)
vg = (# MBR, a, MBR, a, MBR, a, MBR, a, MBR, a #)
-> (# L3 a, L2 a, L2 a, L3 a #)
forall a.
(# MBR, a, MBR, a, MBR, a, MBR, a, MBR, a #)
-> (# L3 a, L2 a, L2 a, L3 a #)
group (# MBR, a, MBR, a, MBR, a, MBR, a, MBR, a #)
v
      hg :: (# L3 a, L2 a, L2 a, L3 a #)
hg = (# MBR, a, MBR, a, MBR, a, MBR, a, MBR, a #)
-> (# L3 a, L2 a, L2 a, L3 a #)
forall a.
(# MBR, a, MBR, a, MBR, a, MBR, a, MBR, a #)
-> (# L3 a, L2 a, L2 a, L3 a #)
group (# MBR, a, MBR, a, MBR, a, MBR, a, MBR, a #)
h

      !(# al :: L3 a
al@(L3 MBR
bu MBR
_ a
_ MBR
_ a
_ MBR
_ a
_), ar :: L2 a
ar@(L2 MBR
bv MBR
_ a
_ MBR
_ a
_)
       , bl :: L2 a
bl@(L2 MBR
bx MBR
_ a
_ MBR
_ a
_), br :: L3 a
br@(L3 MBR
by MBR
_ a
_ MBR
_ a
_ MBR
_ a
_) #)
          | (# L3 a, L2 a, L2 a, L3 a #) -> Double
forall a. (# L3 a, L2 a, L2 a, L3 a #) -> Double
margins (# L3 a, L2 a, L2 a, L3 a #)
vg Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
<= (# L3 a, L2 a, L2 a, L3 a #) -> Double
forall a. (# L3 a, L2 a, L2 a, L3 a #) -> Double
margins (# L3 a, L2 a, L2 a, L3 a #)
hg = (# L3 a, L2 a, L2 a, L3 a #)
vg
          | Bool
otherwise                = (# L3 a, L2 a, L2 a, L3 a #)
hg

      aw :: Q3 a
aw = L3 a -> L2 a -> Q3 a
forall a. L3 a -> L2 a -> Q3 a
Q3L L3 a
al L2 a
ar
      bw :: Q3 a
bw = L2 a -> L3 a -> Q3 a
forall a. L2 a -> L3 a -> Q3 a
Q3R L2 a
bl L3 a
br

  in case MBR -> MBR -> Double
overlapMBR MBR
bu MBR
bv Double -> Double -> Ordering
forall a. Ord a => a -> a -> Ordering
`compare` MBR -> MBR -> Double
overlapMBR MBR
bx MBR
by of
       Ordering
GT -> Q3 a
bw
       Ordering
LT -> Q3 a
aw
       Ordering
EQ | MBR -> Double
areaMBR MBR
bu Double -> Double -> Double
forall a. Num a => a -> a -> a
+ MBR -> Double
areaMBR MBR
bv Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
<= MBR -> Double
areaMBR MBR
bx Double -> Double -> Double
forall a. Num a => a -> a -> a
+ MBR -> Double
areaMBR MBR
by -> Q3 a
aw
          | Bool
otherwise                                          -> Q3 a
bw



sort5Distance
  :: MBR
  -> MBR -> a -> MBR -> a -> MBR -> a -> MBR -> a -> MBR -> a
  -> (# MBR, a, MBR, a, MBR, a, MBR, a, MBR, a #)
sort5Distance :: forall a.
MBR
-> MBR
-> a
-> MBR
-> a
-> MBR
-> a
-> MBR
-> a
-> MBR
-> a
-> (# MBR, a, MBR, a, MBR, a, MBR, a, MBR, a #)
sort5Distance MBR
bx MBR
ka a
a MBR
kb a
b MBR
kc a
c MBR
kd a
d MBR
ke a
e =
  (MBR -> MBR -> Bool)
-> MBR
-> a
-> MBR
-> a
-> MBR
-> a
-> MBR
-> a
-> MBR
-> a
-> (# MBR, a, MBR, a, MBR, a, MBR, a, MBR, a #)
forall k a.
(k -> k -> Bool)
-> k
-> a
-> k
-> a
-> k
-> a
-> k
-> a
-> k
-> a
-> (# k, a, k, a, k, a, k, a, k, a #)
sort5_ (MBR -> MBR -> MBR -> Bool
distance MBR
bx) MBR
ka a
a MBR
kb a
b MBR
kc a
c MBR
kd a
d MBR
ke a
e




{-# INLINE horizontal #-}
horizontal :: MBR -> MBR -> Bool
horizontal :: MBR -> MBR -> Bool
horizontal (UnsafeMBR Double
xmin Double
_ Double
xmax Double
_) (UnsafeMBR Double
xmin' Double
_ Double
xmax' Double
_) =
  case Double
xmin Double -> Double -> Ordering
forall a. Ord a => a -> a -> Ordering
`compare` Double
xmin' of
    Ordering
GT -> Bool
False
    Ordering
LT -> Bool
True
    Ordering
EQ -> Double
xmax Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
<= Double
xmax'

{-# INLINE vertical #-}
vertical :: MBR -> MBR -> Bool
vertical :: MBR -> MBR -> Bool
vertical (UnsafeMBR Double
_ Double
ymin Double
_ Double
ymax) (UnsafeMBR Double
_ Double
ymin' Double
_ Double
ymax') =
  case Double
ymin Double -> Double -> Ordering
forall a. Ord a => a -> a -> Ordering
`compare` Double
ymin' of
    Ordering
GT -> Bool
False
    Ordering
LT -> Bool
True
    Ordering
EQ -> Double
ymax Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
<= Double
ymax'

{-# INLINE distance #-}
distance :: MBR -> MBR -> MBR -> Bool
distance :: MBR -> MBR -> MBR -> Bool
distance MBR
bx MBR
ba MBR
bb = MBR -> MBR -> Double
distanceMBR MBR
bx MBR
ba Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
<= MBR -> MBR -> Double
distanceMBR MBR
bx MBR
bb

{-# INLINE sort5_ #-}
sort5_
  :: (k -> k -> Bool) -- as in (A is smaller than B)
  -> k -> a -> k -> a -> k -> a -> k -> a -> k -> a
  -> (# k, a, k, a, k, a, k, a, k, a #)
sort5_ :: forall k a.
(k -> k -> Bool)
-> k
-> a
-> k
-> a
-> k
-> a
-> k
-> a
-> k
-> a
-> (# k, a, k, a, k, a, k, a, k, a #)
sort5_ k -> k -> Bool
f k
ka a
a k
kb a
b k
kc a
c k
kd a
d k
ke a
e =
  let swap :: k -> b -> k -> b -> (# k, b, k, b #)
swap k
kx b
x k
ky b
y
        | k -> k -> Bool
f k
kx k
ky   = (# k
kx, b
x, k
ky, b
y #)
        | Bool
otherwise = (# k
ky, b
y, k
kx, b
x #)

      sort3 :: k
-> b -> k -> b -> k -> b -> k -> b -> (# k, b, k, b, k, b, k, b #)
sort3 k
kw b
w k
kx b
x k
ky b
y k
kz b
z
        | k -> k -> Bool
f k
kw k
ky  =
            if k -> k -> Bool
f k
kw k
kx
              then (# k
kw, b
w, k
kx, b
x, k
ky, b
y, k
kz, b
z #)
              else (# k
kx, b
x, k
kw, b
w, k
ky, b
y, k
kz, b
z #)

        | Bool
otherwise =
            if k -> k -> Bool
f k
kw k
kz
              then (# k
kx, b
x, k
ky, b
y, k
kw, b
w, k
kz, b
z #)
              else (# k
kx, b
x, k
ky, b
y, k
kz, b
z, k
kw, b
w #)

      (# k
ka1, a
a1, k
kb1, a
b1 #) = k -> a -> k -> a -> (# k, a, k, a #)
forall {b}. k -> b -> k -> b -> (# k, b, k, b #)
swap k
ka a
a k
kb a
b
      (# k
kc1, a
c1, k
kd1, a
d1 #) = k -> a -> k -> a -> (# k, a, k, a #)
forall {b}. k -> b -> k -> b -> (# k, b, k, b #)
swap k
kc a
c k
kd a
d

      (# k
ka2, (a
a2, k
kb2, a
b2), k
kc2, (a
c2, k
kd2, a
d2) #) =
        k
-> (a, k, a) -> k -> (a, k, a) -> (# k, (a, k, a), k, (a, k, a) #)
forall {b}. k -> b -> k -> b -> (# k, b, k, b #)
swap k
ka1 (a
a1, k
kb1, a
b1) k
kc1 (a
c1, k
kd1, a
d1)

      (# k
ka3, a
a3, k
kc3, a
c3, k
kd3, a
d3, k
ke3, a
e3 #) = k
-> a -> k -> a -> k -> a -> k -> a -> (# k, a, k, a, k, a, k, a #)
forall {b}.
k
-> b -> k -> b -> k -> b -> k -> b -> (# k, b, k, b, k, b, k, b #)
sort3 k
ke a
e k
ka2 a
a2 k
kc2 a
c2 k
kd2 a
d2

      (# k
kb4, a
b4, k
kc4, a
c4, k
kd4, a
d4, k
ke4, a
e4 #) = k
-> a -> k -> a -> k -> a -> k -> a -> (# k, a, k, a, k, a, k, a #)
forall {b}.
k
-> b -> k -> b -> k -> b -> k -> b -> (# k, b, k, b, k, b, k, b #)
sort3 k
kb2 a
b2 k
kc3 a
c3 k
kd3 a
d3 k
ke3 a
e3

  in (# k
ka3, a
a3, k
kb4, a
b4, k
kc4, a
c4, k
kd4, a
d4, k
ke4, a
e4 #)

{-# INLINE group #-}
group
  :: (# MBR, a, MBR, a, MBR, a, MBR, a, MBR, a #) -> (# L3 a, L2 a, L2 a, L3 a #)
group :: forall a.
(# MBR, a, MBR, a, MBR, a, MBR, a, MBR, a #)
-> (# L3 a, L2 a, L2 a, L3 a #)
group (# MBR
ba, a
a, MBR
bb, a
b, MBR
bc, a
c, MBR
bd, a
d, MBR
be, a
e #) =
  (# MBR -> MBR -> a -> MBR -> a -> MBR -> a -> L3 a
forall a. MBR -> MBR -> a -> MBR -> a -> MBR -> a -> L3 a
L3 (MBR -> MBR -> MBR -> MBR
union3MBR MBR
ba MBR
bb MBR
bc) MBR
ba a
a MBR
bb a
b MBR
bc a
c, MBR -> MBR -> a -> MBR -> a -> L2 a
forall a. MBR -> MBR -> a -> MBR -> a -> L2 a
L2 (MBR -> MBR -> MBR
unionMBR MBR
bd MBR
be) MBR
bd a
d MBR
be a
e
   , MBR -> MBR -> a -> MBR -> a -> L2 a
forall a. MBR -> MBR -> a -> MBR -> a -> L2 a
L2 (MBR -> MBR -> MBR
unionMBR MBR
ba MBR
bb) MBR
ba a
a MBR
bb a
b, MBR -> MBR -> a -> MBR -> a -> MBR -> a -> L3 a
forall a. MBR -> MBR -> a -> MBR -> a -> MBR -> a -> L3 a
L3 (MBR -> MBR -> MBR -> MBR
union3MBR MBR
bd MBR
be MBR
bc) MBR
bd a
d MBR
be a
e MBR
bc a
c #)

{-# INLINE margins #-}
margins :: (# L3 a, L2 a, L2 a, L3 a #) -> Double
margins :: forall a. (# L3 a, L2 a, L2 a, L3 a #) -> Double
margins (# L3 MBR
bw MBR
_ a
_ MBR
_ a
_ MBR
_ a
_, L2 MBR
bx MBR
_ a
_ MBR
_ a
_, L2 MBR
by MBR
_ a
_ MBR
_ a
_, L3 MBR
bz MBR
_ a
_ MBR
_ a
_ MBR
_ a
_ #) =
  MBR -> Double
marginMBR MBR
bw Double -> Double -> Double
forall a. Num a => a -> a -> a
+ MBR -> Double
marginMBR MBR
bx Double -> Double -> Double
forall a. Num a => a -> a -> a
+ MBR -> Double
marginMBR MBR
by Double -> Double -> Double
forall a. Num a => a -> a -> a
+ MBR -> Double
marginMBR MBR
bz



-- | \(\mathcal{O}(\log n)\).
--   Remove an entry stored under a given t'MBR', if one exists.
--   If multiple entries qualify, the leftmost one is removed.
--
--   'delete' uses the R-tree deletion algorithm with quadratic-cost splits.
delete :: MBR -> R2Tree a -> R2Tree a
delete :: forall a. MBR -> R2Tree a -> R2Tree a
delete MBR
bx R2Tree a
s =
  case MBR -> Int -> R2Tree a -> Del a
forall a. MBR -> Int -> R2Tree a -> Del a
delete_ MBR
bx Int
0 R2Tree a
s of
    DelOne MBR
_ R2Tree a
o     -> R2Tree a
o
    Del a
DelNone        -> R2Tree a
s
    DelSome Re a
re MBR
_ R2Tree a
o -> Int -> R2Tree a -> Re a -> R2Tree a
forall {a}. Int -> R2Tree a -> Re a -> R2Tree a
reintegrate Int
0 R2Tree a
o Re a
re
    DelRe Re a
re       ->
      case Re a
re of
        ReCons Int
_ MBR
_ R2Tree a
n Re a
re' -> Int -> R2Tree a -> Re a -> R2Tree a
forall {a}. Int -> R2Tree a -> Re a -> R2Tree a
reintegrate (-Int
1) R2Tree a
n Re a
re'
        ReLeaf MBR
ba a
a      -> MBR -> a -> R2Tree a
forall a. MBR -> a -> R2Tree a
Leaf1 MBR
ba a
a
  where
    reintegrate :: Int -> R2Tree a -> Re a -> R2Tree a
reintegrate Int
height R2Tree a
n Re a
re =
      case Re a
re of
        ReCons Int
depth MBR
ba R2Tree a
a Re a
re' ->
          case MBR -> R2Tree a -> Int -> R2Tree a -> Gut a
forall a. MBR -> R2Tree a -> Int -> R2Tree a -> Gut a
insertGutRootNode MBR
ba R2Tree a
a (Int
depth Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
height) R2Tree a
n of
            GutOne MBR
_ R2Tree a
o       -> Int -> R2Tree a -> Re a -> R2Tree a
reintegrate Int
height R2Tree a
o Re a
re'
            GutTwo MBR
bl R2Tree a
l MBR
br R2Tree a
r -> Int -> R2Tree a -> Re a -> R2Tree a
reintegrate (Int
height Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) (MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
forall a. MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node2 MBR
bl R2Tree a
l MBR
br R2Tree a
r) Re a
re'

        ReLeaf MBR
ba a
a          ->
          case MBR -> a -> R2Tree a -> Gut a
forall a. MBR -> a -> R2Tree a -> Gut a
insertGutRoot MBR
ba a
a R2Tree a
n of
            GutOne MBR
_ R2Tree a
o       -> R2Tree a
o
            GutTwo MBR
bl R2Tree a
l MBR
br R2Tree a
r -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
forall a. MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node2 MBR
bl R2Tree a
l MBR
br R2Tree a
r



data Re a = ReCons Int MBR (R2Tree a) (Re a)
          | ReLeaf MBR a

data Del a = DelNone
           | DelOne MBR (R2Tree a)
           | DelSome (Re a) MBR (R2Tree a)
           | DelRe (Re a)

delete_ :: MBR -> Int -> R2Tree a -> Del a
delete_ :: forall a. MBR -> Int -> R2Tree a -> Del a
delete_ MBR
bx = Int -> R2Tree a -> Del a
forall {a}. Int -> R2Tree a -> Del a
go
  where
    {-# INLINE cut2 #-}
    cut2 :: Int -> Del a -> MBR -> R2Tree a -> MBR -> R2Tree a -> Del a
cut2 Int
depth Del a
next MBR
ba R2Tree a
a MBR
bb R2Tree a
b
      | MBR -> MBR -> Bool
containsMBR MBR
ba MBR
bx =
          case Int -> R2Tree a -> Del a
go (Int
depth Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) R2Tree a
a of
            Del a
DelNone         -> Del a
next
            DelOne MBR
bo R2Tree a
o     -> MBR -> R2Tree a -> Del a
forall a. MBR -> R2Tree a -> Del a
DelOne (MBR -> MBR -> MBR
unionMBR MBR
bo MBR
bb) (MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
forall a. MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node2 MBR
bo R2Tree a
o MBR
bb R2Tree a
b)
            DelSome Re a
re MBR
bo R2Tree a
o -> Re a -> MBR -> R2Tree a -> Del a
forall a. Re a -> MBR -> R2Tree a -> Del a
DelSome Re a
re (MBR -> MBR -> MBR
unionMBR MBR
bo MBR
bb) (MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
forall a. MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node2 MBR
bo R2Tree a
o MBR
bb R2Tree a
b)
            DelRe Re a
re        -> Re a -> Del a
forall a. Re a -> Del a
DelRe (Int -> MBR -> R2Tree a -> Re a -> Re a
forall a. Int -> MBR -> R2Tree a -> Re a -> Re a
ReCons Int
depth MBR
bb R2Tree a
b Re a
re)

      | Bool
otherwise         = Del a
next

    {-# INLINE cut3 #-}
    cut3 :: Int
-> Del a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> Del a
cut3 Int
depth Del a
next MBR
ba R2Tree a
a MBR
bb R2Tree a
b MBR
bc R2Tree a
c
      | MBR -> MBR -> Bool
containsMBR MBR
ba MBR
bx =
          case Int -> R2Tree a -> Del a
go (Int
depth Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) R2Tree a
a of
            Del a
DelNone         -> Del a
next
            DelOne MBR
bo R2Tree a
o     -> MBR -> R2Tree a -> Del a
forall a. MBR -> R2Tree a -> Del a
DelOne (MBR -> MBR -> MBR -> MBR
union3MBR MBR
bo MBR
bb MBR
bc) (MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
forall a.
MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node3 MBR
bo R2Tree a
o MBR
bb R2Tree a
b MBR
bc R2Tree a
c)
            DelSome Re a
re MBR
bo R2Tree a
o -> Re a -> MBR -> R2Tree a -> Del a
forall a. Re a -> MBR -> R2Tree a -> Del a
DelSome Re a
re (MBR -> MBR -> MBR -> MBR
union3MBR MBR
bo MBR
bb MBR
bc) (MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
forall a.
MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node3 MBR
bo R2Tree a
o MBR
bb R2Tree a
b MBR
bc R2Tree a
c)
            DelRe Re a
re        -> Re a -> MBR -> R2Tree a -> Del a
forall a. Re a -> MBR -> R2Tree a -> Del a
DelSome Re a
re (MBR -> MBR -> MBR
unionMBR MBR
bb MBR
bc) (MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
forall a. MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node2 MBR
bb R2Tree a
b MBR
bc R2Tree a
c)

      | Bool
otherwise         = Del a
next

    {-# INLINE cut4 #-}
    cut4 :: Int
-> Del a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> Del a
cut4 Int
depth Del a
next MBR
ba R2Tree a
a MBR
bb R2Tree a
b MBR
bc R2Tree a
c MBR
bd R2Tree a
d
      | MBR -> MBR -> Bool
containsMBR MBR
ba MBR
bx =
          case Int -> R2Tree a -> Del a
go (Int
depth Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) R2Tree a
a of
            Del a
DelNone         -> Del a
next
            DelOne MBR
bo R2Tree a
o     -> MBR -> R2Tree a -> Del a
forall a. MBR -> R2Tree a -> Del a
DelOne (MBR -> MBR -> MBR -> MBR -> MBR
union4MBR MBR
bo MBR
bb MBR
bc MBR
bd) (MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> R2Tree a
forall a.
MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> R2Tree a
Node4 MBR
bo R2Tree a
o MBR
bb R2Tree a
b MBR
bc R2Tree a
c MBR
bd R2Tree a
d)
            DelSome Re a
re MBR
bo R2Tree a
o -> Re a -> MBR -> R2Tree a -> Del a
forall a. Re a -> MBR -> R2Tree a -> Del a
DelSome Re a
re (MBR -> MBR -> MBR -> MBR -> MBR
union4MBR MBR
bo MBR
bb MBR
bc MBR
bd) (MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> R2Tree a
forall a.
MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> R2Tree a
Node4 MBR
bo R2Tree a
o MBR
bb R2Tree a
b MBR
bc R2Tree a
c MBR
bd R2Tree a
d)
            DelRe Re a
re        -> Re a -> MBR -> R2Tree a -> Del a
forall a. Re a -> MBR -> R2Tree a -> Del a
DelSome Re a
re (MBR -> MBR -> MBR -> MBR
union3MBR MBR
bb MBR
bc MBR
bd) (MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
forall a.
MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node3 MBR
bb R2Tree a
b MBR
bc R2Tree a
c MBR
bd R2Tree a
d)

      | Bool
otherwise         = Del a
next

    {-# INLINE edge2 #-}
    edge2 :: Del a -> MBR -> MBR -> a -> Del a
edge2 Del a
next MBR
ba MBR
bb a
b
      | MBR -> MBR -> Bool
eqMBR MBR
ba MBR
bx = Re a -> Del a
forall a. Re a -> Del a
DelRe (MBR -> a -> Re a
forall a. MBR -> a -> Re a
ReLeaf MBR
bb a
b)
      | Bool
otherwise   = Del a
next

    {-# INLINE edge3 #-}
    edge3 :: Del a -> MBR -> MBR -> a -> MBR -> a -> Del a
edge3 Del a
next MBR
ba MBR
bb a
b MBR
bc a
c
      | MBR -> MBR -> Bool
eqMBR MBR
ba MBR
bx = MBR -> R2Tree a -> Del a
forall a. MBR -> R2Tree a -> Del a
DelOne (MBR -> MBR -> MBR
unionMBR MBR
bb MBR
bc) (MBR -> a -> MBR -> a -> R2Tree a
forall a. MBR -> a -> MBR -> a -> R2Tree a
Leaf2 MBR
bb a
b MBR
bc a
c)
      | Bool
otherwise   = Del a
next

    {-# INLINE edge4 #-}
    edge4 :: Del a -> MBR -> MBR -> a -> MBR -> a -> MBR -> a -> Del a
edge4 Del a
next MBR
ba MBR
bb a
b MBR
bc a
c MBR
bd a
d
      | MBR -> MBR -> Bool
eqMBR MBR
ba MBR
bx = MBR -> R2Tree a -> Del a
forall a. MBR -> R2Tree a -> Del a
DelOne (MBR -> MBR -> MBR -> MBR
union3MBR MBR
bb MBR
bc MBR
bd) (MBR -> a -> MBR -> a -> MBR -> a -> R2Tree a
forall a. MBR -> a -> MBR -> a -> MBR -> a -> R2Tree a
Leaf3 MBR
bb a
b MBR
bc a
c MBR
bd a
d)
      | Bool
otherwise   = Del a
next

    go :: Int -> R2Tree a -> Del a
go Int
depth R2Tree a
n =
      case R2Tree a
n of
        Node2 MBR
ba R2Tree a
a MBR
bb R2Tree a
b ->
          let dela :: Del a
dela = Int -> Del a -> MBR -> R2Tree a -> MBR -> R2Tree a -> Del a
cut2 Int
depth Del a
delb    MBR
ba R2Tree a
a MBR
bb R2Tree a
b
              delb :: Del a
delb = Int -> Del a -> MBR -> R2Tree a -> MBR -> R2Tree a -> Del a
cut2 Int
depth Del a
forall a. Del a
DelNone MBR
bb R2Tree a
b MBR
ba R2Tree a
a

          in Del a
dela

        Node3 MBR
ba R2Tree a
a MBR
bb R2Tree a
b MBR
bc R2Tree a
c ->
          let dela :: Del a
dela = Int
-> Del a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> Del a
cut3 Int
depth Del a
delb    MBR
ba R2Tree a
a MBR
bb R2Tree a
b MBR
bc R2Tree a
c
              delb :: Del a
delb = Int
-> Del a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> Del a
cut3 Int
depth Del a
delc    MBR
bb R2Tree a
b MBR
ba R2Tree a
a MBR
bc R2Tree a
c
              delc :: Del a
delc = Int
-> Del a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> Del a
cut3 Int
depth Del a
forall a. Del a
DelNone MBR
bc R2Tree a
c MBR
ba R2Tree a
a MBR
bb R2Tree a
b

          in Del a
dela

        Node4 MBR
ba R2Tree a
a MBR
bb R2Tree a
b MBR
bc R2Tree a
c MBR
bd R2Tree a
d ->
          let dela :: Del a
dela = Int
-> Del a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> Del a
cut4 Int
depth Del a
delb    MBR
ba R2Tree a
a MBR
bb R2Tree a
b MBR
bc R2Tree a
c MBR
bd R2Tree a
d
              delb :: Del a
delb = Int
-> Del a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> Del a
cut4 Int
depth Del a
delc    MBR
bb R2Tree a
b MBR
ba R2Tree a
a MBR
bc R2Tree a
c MBR
bd R2Tree a
d
              delc :: Del a
delc = Int
-> Del a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> Del a
cut4 Int
depth Del a
deld    MBR
bc R2Tree a
c MBR
ba R2Tree a
a MBR
bb R2Tree a
b MBR
bd R2Tree a
d
              deld :: Del a
deld = Int
-> Del a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> Del a
cut4 Int
depth Del a
forall a. Del a
DelNone MBR
bd R2Tree a
d MBR
ba R2Tree a
a MBR
bb R2Tree a
b MBR
bc R2Tree a
c

          in Del a
dela

        Leaf2 MBR
ba a
a MBR
bb a
b ->
          let dela :: Del a
dela = Del a -> MBR -> MBR -> a -> Del a
forall {a}. Del a -> MBR -> MBR -> a -> Del a
edge2 Del a
delb    MBR
ba MBR
bb a
b
              delb :: Del a
delb = Del a -> MBR -> MBR -> a -> Del a
forall {a}. Del a -> MBR -> MBR -> a -> Del a
edge2 Del a
forall a. Del a
DelNone MBR
bb MBR
ba a
a

          in Del a
dela

        Leaf3 MBR
ba a
a MBR
bb a
b MBR
bc a
c ->
          let dela :: Del a
dela = Del a -> MBR -> MBR -> a -> MBR -> a -> Del a
forall {a}. Del a -> MBR -> MBR -> a -> MBR -> a -> Del a
edge3 Del a
delb    MBR
ba MBR
bb a
b MBR
bc a
c
              delb :: Del a
delb = Del a -> MBR -> MBR -> a -> MBR -> a -> Del a
forall {a}. Del a -> MBR -> MBR -> a -> MBR -> a -> Del a
edge3 Del a
delc    MBR
bb MBR
ba a
a MBR
bc a
c
              delc :: Del a
delc = Del a -> MBR -> MBR -> a -> MBR -> a -> Del a
forall {a}. Del a -> MBR -> MBR -> a -> MBR -> a -> Del a
edge3 Del a
forall a. Del a
DelNone MBR
bc MBR
ba a
a MBR
bb a
b

          in Del a
dela

        Leaf4 MBR
ba a
a MBR
bb a
b MBR
bc a
c MBR
bd a
d ->
          let dela :: Del a
dela = Del a -> MBR -> MBR -> a -> MBR -> a -> MBR -> a -> Del a
forall {a}.
Del a -> MBR -> MBR -> a -> MBR -> a -> MBR -> a -> Del a
edge4 Del a
delb    MBR
ba MBR
bb a
b MBR
bc a
c MBR
bd a
d
              delb :: Del a
delb = Del a -> MBR -> MBR -> a -> MBR -> a -> MBR -> a -> Del a
forall {a}.
Del a -> MBR -> MBR -> a -> MBR -> a -> MBR -> a -> Del a
edge4 Del a
delc    MBR
bb MBR
ba a
a MBR
bc a
c MBR
bd a
d
              delc :: Del a
delc = Del a -> MBR -> MBR -> a -> MBR -> a -> MBR -> a -> Del a
forall {a}.
Del a -> MBR -> MBR -> a -> MBR -> a -> MBR -> a -> Del a
edge4 Del a
deld    MBR
bc MBR
ba a
a MBR
bb a
b MBR
bd a
d
              deld :: Del a
deld = Del a -> MBR -> MBR -> a -> MBR -> a -> MBR -> a -> Del a
forall {a}.
Del a -> MBR -> MBR -> a -> MBR -> a -> MBR -> a -> Del a
edge4 Del a
forall a. Del a
DelNone MBR
bd MBR
ba a
a MBR
bb a
b MBR
bc a
c

          in Del a
dela

        Leaf1 MBR
ba a
_ | MBR -> MBR -> Bool
eqMBR MBR
bx MBR
ba -> MBR -> R2Tree a -> Del a
forall a. MBR -> R2Tree a -> Del a
DelOne MBR
ba R2Tree a
forall a. R2Tree a
Empty
                   | Bool
otherwise   -> Del a
forall a. Del a
DelNone

        R2Tree a
Empty      -> Del a
forall a. Del a
DelNone




quotCeil :: Int -> Int -> Int
quotCeil :: Int -> Int -> Int
quotCeil Int
i Int
d = let ~(Int
p, Int
q) = Int -> Int -> (Int, Int)
forall a. Integral a => a -> a -> (a, a)
quotRem Int
i Int
d
               in Int
p Int -> Int -> Int
forall a. Num a => a -> a -> a
+ case Int
q of
                        Int
0 -> Int
0
                        Int
_ -> Int
1

slices :: Int -> Int
slices :: Int -> Int
slices Int
r = Double -> Int
forall b. Integral b => Double -> b
forall a b. (RealFrac a, Integral b) => a -> b
ceiling (Double -> Double
forall a. Floating a => a -> a
sqrt (Int -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Int -> Int
quotCeil Int
r Int
4)) :: Double)

partition1 :: Int -> [a] -> [(Int, [a])]
partition1 :: forall a. Int -> [a] -> [(Int, [a])]
partition1 Int
n_ = [a] -> [(Int, [a])]
forall {a}. [a] -> [(Int, [a])]
go
  where
    go :: [a] -> [(Int, [a])]
go [a]
xs =
      let ~(Int
n, [a]
before, [a]
after) = Int -> [a] -> (Int, [a], [a])
forall {a}. Int -> [a] -> (Int, [a], [a])
splitAt1 Int
0 [a]
xs
      in (Int
n, [a]
before) (Int, [a]) -> [(Int, [a])] -> [(Int, [a])]
forall a. a -> [a] -> [a]
: case [a]
after of
                         a
_:[a]
_ -> [a] -> [(Int, [a])]
go [a]
after
                         []  -> []

    splitAt1 :: Int -> [a] -> (Int, [a], [a])
splitAt1 Int
n [a]
xs =
      case [a]
xs of
        []   -> (Int
n, [], [])
        a
x:[a]
ys
          | Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
n_    -> let ~(Int
m, [a]
as, [a]
bs) = Int -> [a] -> (Int, [a], [a])
splitAt1 (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) [a]
ys
                         in (Int
m, a
xa -> [a] -> [a]
forall a. a -> [a] -> [a]
:[a]
as, [a]
bs)

          | [] <- [a]
ys  -> (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1, [a]
xs, [])
          | Bool
otherwise -> (Int
n    , [], [a]
xs)



-- | \(\mathcal{O}(n \log n)\). Bulk-load a tree.
--
--   'bulkSTR' uses the Sort-Tile-Recursive algorithm.
bulkSTR :: [(MBR, a)] -> R2Tree a
bulkSTR :: forall a. [(MBR, a)] -> R2Tree a
bulkSTR [(MBR, a)]
xs =
  case [(MBR, a)]
xs of
    (MBR, a)
_:(MBR, a)
_:[(MBR, a)]
_     -> (MBR, R2Tree a) -> R2Tree a
forall a b. (a, b) -> b
snd ((MBR, R2Tree a) -> R2Tree a) -> (MBR, R2Tree a) -> R2Tree a
forall a b. (a -> b) -> a -> b
$ Int -> [(MBR, a)] -> (MBR, R2Tree a)
forall {b}. Int -> [(MBR, b)] -> (MBR, R2Tree b)
vertically ([(MBR, a)] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [(MBR, a)]
xs) [(MBR, a)]
xs
    [(MBR
ba, a
a)] -> MBR -> a -> R2Tree a
forall a. MBR -> a -> R2Tree a
Leaf1 MBR
ba a
a
    []        -> R2Tree a
forall a. R2Tree a
Empty
  where
    horiCenter :: (MBR, b) -> Double
horiCenter (UnsafeMBR Double
xmin Double
_ Double
xmax Double
_, b
_) = Double
xmin Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double
xmax

    vertCenter :: (MBR, b) -> Double
vertCenter (UnsafeMBR Double
_ Double
ymin Double
_ Double
ymax, b
_) = Double
ymin Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double
ymax

    horizontally :: Int -> [(MBR, b)] -> (MBR, R2Tree b)
horizontally Int
r [(MBR, b)]
as =
      let s :: Int
s = Int -> Int
slices Int
r
      in if Int
s Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
1
           then [(MBR, b)] -> (MBR, R2Tree b)
forall {a}. [(MBR, a)] -> (MBR, R2Tree a)
base [(MBR, b)]
as
           else [(MBR, R2Tree b)] -> (MBR, R2Tree b)
forall {a}. [(MBR, R2Tree a)] -> (MBR, R2Tree a)
compress ([(MBR, R2Tree b)] -> (MBR, R2Tree b))
-> ([(Int, [(MBR, b)])] -> [(MBR, R2Tree b)])
-> [(Int, [(MBR, b)])]
-> (MBR, R2Tree b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                  ((Int, [(MBR, b)]) -> (MBR, R2Tree b))
-> [(Int, [(MBR, b)])] -> [(MBR, R2Tree b)]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Int -> [(MBR, b)] -> (MBR, R2Tree b))
-> (Int, [(MBR, b)]) -> (MBR, R2Tree b)
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry Int -> [(MBR, b)] -> (MBR, R2Tree b)
vertically) ([(Int, [(MBR, b)])] -> (MBR, R2Tree b))
-> [(Int, [(MBR, b)])] -> (MBR, R2Tree b)
forall a b. (a -> b) -> a -> b
$
                    Int -> [(MBR, b)] -> [(Int, [(MBR, b)])]
forall a. Int -> [a] -> [(Int, [a])]
partition1 (Int
r Int -> Int -> Int
`quotCeil` Int
s) (((MBR, b) -> (MBR, b) -> Ordering) -> [(MBR, b)] -> [(MBR, b)]
forall a. (a -> a -> Ordering) -> [a] -> [a]
List.sortBy (Double -> Double -> Ordering
forall a. Ord a => a -> a -> Ordering
compare (Double -> Double -> Ordering)
-> ((MBR, b) -> Double) -> (MBR, b) -> (MBR, b) -> Ordering
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` (MBR, b) -> Double
forall {b}. (MBR, b) -> Double
vertCenter) [(MBR, b)]
as)


    vertically :: Int -> [(MBR, b)] -> (MBR, R2Tree b)
vertically Int
r [(MBR, b)]
as =
      let s :: Int
s = Int -> Int
slices Int
r
      in if Int
s Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
1
           then [(MBR, b)] -> (MBR, R2Tree b)
forall {a}. [(MBR, a)] -> (MBR, R2Tree a)
base [(MBR, b)]
as
           else [(MBR, R2Tree b)] -> (MBR, R2Tree b)
forall {a}. [(MBR, R2Tree a)] -> (MBR, R2Tree a)
compress ([(MBR, R2Tree b)] -> (MBR, R2Tree b))
-> ([(Int, [(MBR, b)])] -> [(MBR, R2Tree b)])
-> [(Int, [(MBR, b)])]
-> (MBR, R2Tree b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                  ((Int, [(MBR, b)]) -> (MBR, R2Tree b))
-> [(Int, [(MBR, b)])] -> [(MBR, R2Tree b)]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Int -> [(MBR, b)] -> (MBR, R2Tree b))
-> (Int, [(MBR, b)]) -> (MBR, R2Tree b)
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry Int -> [(MBR, b)] -> (MBR, R2Tree b)
horizontally) ([(Int, [(MBR, b)])] -> (MBR, R2Tree b))
-> [(Int, [(MBR, b)])] -> (MBR, R2Tree b)
forall a b. (a -> b) -> a -> b
$
                    Int -> [(MBR, b)] -> [(Int, [(MBR, b)])]
forall a. Int -> [a] -> [(Int, [a])]
partition1 (Int
r Int -> Int -> Int
`quotCeil` Int
s) (((MBR, b) -> (MBR, b) -> Ordering) -> [(MBR, b)] -> [(MBR, b)]
forall a. (a -> a -> Ordering) -> [a] -> [a]
List.sortBy (Double -> Double -> Ordering
forall a. Ord a => a -> a -> Ordering
compare (Double -> Double -> Ordering)
-> ((MBR, b) -> Double) -> (MBR, b) -> (MBR, b) -> Ordering
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` (MBR, b) -> Double
forall {b}. (MBR, b) -> Double
horiCenter) [(MBR, b)]
as)

    compress :: [(MBR, R2Tree a)] -> (MBR, R2Tree a)
compress ((MBR, R2Tree a)
x : [(MBR, R2Tree a)]
ys) = NonEmpty (MBR, R2Tree a) -> (MBR, R2Tree a)
forall {a}. NonEmpty (MBR, R2Tree a) -> (MBR, R2Tree a)
go ((MBR, R2Tree a)
x (MBR, R2Tree a) -> [(MBR, R2Tree a)] -> NonEmpty (MBR, R2Tree a)
forall a. a -> [a] -> NonEmpty a
:| [(MBR, R2Tree a)]
ys)
      where
        go :: NonEmpty (MBR, R2Tree a) -> (MBR, R2Tree a)
go ((MBR, R2Tree a)
a :| [(MBR, R2Tree a)]
bs) =
          case [(MBR, R2Tree a)]
bs of
            []   -> (MBR, R2Tree a)
a
            (MBR, R2Tree a)
b:[(MBR, R2Tree a)]
cs -> NonEmpty (MBR, R2Tree a) -> (MBR, R2Tree a)
go ((MBR, R2Tree a)
-> (MBR, R2Tree a) -> [(MBR, R2Tree a)] -> NonEmpty (MBR, R2Tree a)
forall {a}.
(MBR, R2Tree a)
-> (MBR, R2Tree a) -> [(MBR, R2Tree a)] -> NonEmpty (MBR, R2Tree a)
mend (MBR, R2Tree a)
a (MBR, R2Tree a)
b [(MBR, R2Tree a)]
cs)

    compress [] =
      String -> (MBR, R2Tree a)
forall a. String -> a
errorWithoutStackTrace
        String
"Data.R2Tree.Double.Internal.bulkSTR: zero-sized partition"

    mend :: (MBR, R2Tree a)
-> (MBR, R2Tree a) -> [(MBR, R2Tree a)] -> NonEmpty (MBR, R2Tree a)
mend (MBR
ba, R2Tree a
a) (MBR
bb, R2Tree a
b) [(MBR, R2Tree a)]
cs =
      case [(MBR, R2Tree a)]
cs of
        (MBR
bc, R2Tree a
c) : (MBR
bd, R2Tree a
d) : (MBR, R2Tree a)
e : (MBR, R2Tree a)
f : [(MBR, R2Tree a)]
gs ->
          (MBR -> MBR -> MBR -> MBR -> MBR
union4MBR MBR
ba MBR
bb MBR
bc MBR
bd, MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> R2Tree a
forall a.
MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> R2Tree a
Node4 MBR
ba R2Tree a
a MBR
bb R2Tree a
b MBR
bc R2Tree a
c MBR
bd R2Tree a
d) (MBR, R2Tree a)
-> NonEmpty (MBR, R2Tree a) -> NonEmpty (MBR, R2Tree a)
forall a. a -> NonEmpty a -> NonEmpty a
<| (MBR, R2Tree a)
-> (MBR, R2Tree a) -> [(MBR, R2Tree a)] -> NonEmpty (MBR, R2Tree a)
mend (MBR, R2Tree a)
e (MBR, R2Tree a)
f [(MBR, R2Tree a)]
gs

        (MBR
bc, R2Tree a
c) : (MBR
bd, R2Tree a
d) : (MBR
be, R2Tree a
e) : [] ->
          (MBR -> MBR -> MBR -> MBR
union3MBR MBR
ba MBR
bb MBR
bc, MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
forall a.
MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node3 MBR
ba R2Tree a
a MBR
bb R2Tree a
b MBR
bc R2Tree a
c) (MBR, R2Tree a) -> [(MBR, R2Tree a)] -> NonEmpty (MBR, R2Tree a)
forall a. a -> [a] -> NonEmpty a
:|
            (MBR -> MBR -> MBR
unionMBR MBR
bd MBR
be, MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
forall a. MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node2 MBR
bd R2Tree a
d MBR
be R2Tree a
e) (MBR, R2Tree a) -> [(MBR, R2Tree a)] -> [(MBR, R2Tree a)]
forall a. a -> [a] -> [a]
: []

        (MBR
bc, R2Tree a
c) : (MBR
bd, R2Tree a
d) : [] ->
          (MBR -> MBR -> MBR -> MBR -> MBR
union4MBR MBR
ba MBR
bb MBR
bc MBR
bd, MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> R2Tree a
forall a.
MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> MBR
-> R2Tree a
-> R2Tree a
Node4 MBR
ba R2Tree a
a MBR
bb R2Tree a
b MBR
bc R2Tree a
c MBR
bd R2Tree a
d) (MBR, R2Tree a) -> [(MBR, R2Tree a)] -> NonEmpty (MBR, R2Tree a)
forall a. a -> [a] -> NonEmpty a
:| []

        (MBR
bc, R2Tree a
c) : [] ->
          (MBR -> MBR -> MBR -> MBR
union3MBR MBR
ba MBR
bb MBR
bc, MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
forall a.
MBR -> R2Tree a -> MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node3 MBR
ba R2Tree a
a MBR
bb R2Tree a
b MBR
bc R2Tree a
c) (MBR, R2Tree a) -> [(MBR, R2Tree a)] -> NonEmpty (MBR, R2Tree a)
forall a. a -> [a] -> NonEmpty a
:| []

        [] ->
          (MBR -> MBR -> MBR
unionMBR MBR
ba MBR
bb, MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
forall a. MBR -> R2Tree a -> MBR -> R2Tree a -> R2Tree a
Node2 MBR
ba R2Tree a
a MBR
bb R2Tree a
b) (MBR, R2Tree a) -> [(MBR, R2Tree a)] -> NonEmpty (MBR, R2Tree a)
forall a. a -> [a] -> NonEmpty a
:| []

    base :: [(MBR, a)] -> (MBR, R2Tree a)
base [(MBR, a)]
as =
      case [(MBR, a)]
as of
        (MBR
ba, a
a) : (MBR
bb, a
b) : (MBR
bc, a
c) : (MBR
bd, a
d) : [] ->
          (MBR -> MBR -> MBR -> MBR -> MBR
union4MBR MBR
ba MBR
bb MBR
bc MBR
bd, MBR -> a -> MBR -> a -> MBR -> a -> MBR -> a -> R2Tree a
forall a. MBR -> a -> MBR -> a -> MBR -> a -> MBR -> a -> R2Tree a
Leaf4 MBR
ba a
a MBR
bb a
b MBR
bc a
c MBR
bd a
d)

        (MBR
ba, a
a) : (MBR
bb, a
b) : (MBR
bc, a
c) : [] ->
          (MBR -> MBR -> MBR -> MBR
union3MBR MBR
ba MBR
bb MBR
bc, MBR -> a -> MBR -> a -> MBR -> a -> R2Tree a
forall a. MBR -> a -> MBR -> a -> MBR -> a -> R2Tree a
Leaf3 MBR
ba a
a MBR
bb a
b MBR
bc a
c)

        (MBR
ba, a
a) : (MBR
bb, a
b) : [] ->
          (MBR -> MBR -> MBR
unionMBR MBR
ba MBR
bb, MBR -> a -> MBR -> a -> R2Tree a
forall a. MBR -> a -> MBR -> a -> R2Tree a
Leaf2 MBR
ba a
a MBR
bb a
b)

        [(MBR, a)]
_ -> String -> (MBR, R2Tree a)
forall a. String -> a
errorWithoutStackTrace
               String
"Data.R2Tree.Double.Internal.bulkSTR: malformed leaf"