module Data.Tree.AVL.Internals.HSet
(
unionH,unionMaybeH,disjointUnionH,
intersectionH,intersectionMaybeH,
differenceH,differenceMaybeH,symDifferenceH,
vennH,vennMaybeH,
) where
import Data.Tree.AVL.Internals.Types(AVL(..))
import Data.Tree.AVL.Internals.HJoin(spliceH,joinH)
import Data.COrdering
import GHC.Base
#include "ghcdefs.h"
unionH :: (e -> e -> COrdering e) -> AVL e -> UINT -> AVL e -> UINT -> UBT2(AVL e,UINT)
unionH :: forall e.
(e -> e -> COrdering e)
-> AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
unionH e -> e -> COrdering e
c = AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
u where
u :: AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
u AVL e
E Int#
_ AVL e
t1 Int#
h1 = UBT2(t1,h1)
u AVL e
t0 Int#
h0 AVL e
E Int#
_ = UBT2(t0,h0)
u (N AVL e
l0 e
e0 AVL e
r0) Int#
h0 (N AVL e
l1 e
e1 AVL e
r1) Int#
h1 = AVL e
-> Int#
-> e
-> AVL e
-> Int#
-> AVL e
-> Int#
-> e
-> AVL e
-> Int#
-> (# AVL e, Int# #)
u_ AVL e
l0 DECINT2(h0) e0 r0 DECINT1(h0) l1 DECINT2(h1) AVL e
e1 r1 DECINT1(h1)
u (N AVL e
l0 e
e0 AVL e
r0) Int#
h0 (Z AVL e
l1 e
e1 AVL e
r1) Int#
h1 = AVL e
-> Int#
-> e
-> AVL e
-> Int#
-> AVL e
-> Int#
-> e
-> AVL e
-> Int#
-> (# AVL e, Int# #)
u_ AVL e
l0 DECINT2(h0) e0 r0 DECINT1(h0) l1 DECINT1(h1) AVL e
e1 r1 DECINT1(h1)
u (N AVL e
l0 e
e0 AVL e
r0) Int#
h0 (P AVL e
l1 e
e1 AVL e
r1) Int#
h1 = AVL e
-> Int#
-> e
-> AVL e
-> Int#
-> AVL e
-> Int#
-> e
-> AVL e
-> Int#
-> (# AVL e, Int# #)
u_ AVL e
l0 DECINT2(h0) e0 r0 DECINT1(h0) l1 DECINT1(h1) AVL e
e1 r1 DECINT2(h1)
u (Z AVL e
l0 e
e0 AVL e
r0) Int#
h0 (N AVL e
l1 e
e1 AVL e
r1) Int#
h1 = AVL e
-> Int#
-> e
-> AVL e
-> Int#
-> AVL e
-> Int#
-> e
-> AVL e
-> Int#
-> (# AVL e, Int# #)
u_ AVL e
l0 DECINT1(h0) e0 r0 DECINT1(h0) l1 DECINT2(h1) AVL e
e1 r1 DECINT1(h1)
u (Z AVL e
l0 e
e0 AVL e
r0) Int#
h0 (Z AVL e
l1 e
e1 AVL e
r1) Int#
h1 = AVL e
-> Int#
-> e
-> AVL e
-> Int#
-> AVL e
-> Int#
-> e
-> AVL e
-> Int#
-> (# AVL e, Int# #)
u_ AVL e
l0 DECINT1(h0) e0 r0 DECINT1(h0) l1 DECINT1(h1) AVL e
e1 r1 DECINT1(h1)
u (Z AVL e
l0 e
e0 AVL e
r0) Int#
h0 (P AVL e
l1 e
e1 AVL e
r1) Int#
h1 = AVL e
-> Int#
-> e
-> AVL e
-> Int#
-> AVL e
-> Int#
-> e
-> AVL e
-> Int#
-> (# AVL e, Int# #)
u_ AVL e
l0 DECINT1(h0) e0 r0 DECINT1(h0) l1 DECINT1(h1) AVL e
e1 r1 DECINT2(h1)
u (P AVL e
l0 e
e0 AVL e
r0) Int#
h0 (N AVL e
l1 e
e1 AVL e
r1) Int#
h1 = AVL e
-> Int#
-> e
-> AVL e
-> Int#
-> AVL e
-> Int#
-> e
-> AVL e
-> Int#
-> (# AVL e, Int# #)
u_ AVL e
l0 DECINT1(h0) e0 r0 DECINT2(h0) l1 DECINT2(h1) AVL e
e1 r1 DECINT1(h1)
u (P AVL e
l0 e
e0 AVL e
r0) Int#
h0 (Z AVL e
l1 e
e1 AVL e
r1) Int#
h1 = AVL e
-> Int#
-> e
-> AVL e
-> Int#
-> AVL e
-> Int#
-> e
-> AVL e
-> Int#
-> (# AVL e, Int# #)
u_ AVL e
l0 DECINT1(h0) e0 r0 DECINT2(h0) l1 DECINT1(h1) AVL e
e1 r1 DECINT1(h1)
u (P AVL e
l0 e
e0 AVL e
r0) Int#
h0 (P AVL e
l1 e
e1 AVL e
r1) Int#
h1 = AVL e
-> Int#
-> e
-> AVL e
-> Int#
-> AVL e
-> Int#
-> e
-> AVL e
-> Int#
-> (# AVL e, Int# #)
u_ AVL e
l0 DECINT1(h0) e0 r0 DECINT2(h0) l1 DECINT1(h1) AVL e
e1 r1 DECINT2(h1)
u_ :: AVL e
-> Int#
-> e
-> AVL e
-> Int#
-> AVL e
-> Int#
-> e
-> AVL e
-> Int#
-> (# AVL e, Int# #)
u_ AVL e
l0 Int#
hl0 e
e0 AVL e
r0 Int#
hr0 AVL e
l1 Int#
hl1 e
e1 AVL e
r1 Int#
hr1 =
case e -> e -> COrdering e
c e
e0 e
e1 of
COrdering e
Lt -> case AVL e -> Int# -> e -> (# AVL e, Int#, e, AVL e, Int# #)
forkR AVL e
r0 Int#
hr0 e
e1 of
UBT5(rl0,hrl0,e1_,rr0,hrr0) -> case e -> AVL e -> Int# -> (# AVL e, Int#, e, AVL e, Int# #)
forkL e
e0 AVL e
l1 Int#
hl1 of
UBT5(ll1,hll1,e0_,lr1,hlr1) ->
case AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
u AVL e
l0 Int#
hl0 AVL e
ll1 Int#
hll1 of
UBT2(l,hl) -> case AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
u AVL e
rl0 Int#
hrl0 AVL e
lr1 Int#
hlr1 of
UBT2(m,hm) -> case AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
u AVL e
rr0 Int#
hrr0 AVL e
r1 Int#
hr1 of
UBT2(r,hr) -> case AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
forall e. AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
spliceH AVL e
m Int#
hm e
e1_ AVL e
r Int#
hr of
UBT2(t,ht) -> AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
forall e. AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
spliceH AVL e
l Int#
hl e
e0_ AVL e
t Int#
ht
Eq e
e -> case AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
u AVL e
l0 Int#
hl0 AVL e
l1 Int#
hl1 of
UBT2(l,hl) -> case AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
u AVL e
r0 Int#
hr0 AVL e
r1 Int#
hr1 of
UBT2(r,hr) -> AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
forall e. AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
spliceH AVL e
l Int#
hl e
e AVL e
r Int#
hr
COrdering e
Gt -> case e -> AVL e -> Int# -> (# AVL e, Int#, e, AVL e, Int# #)
forkL e
e0 AVL e
r1 Int#
hr1 of
UBT5(rl1,hrl1,e0_,rr1,hrr1) -> case AVL e -> Int# -> e -> (# AVL e, Int#, e, AVL e, Int# #)
forkR AVL e
l0 Int#
hl0 e
e1 of
UBT5(ll0,hll0,e1_,lr0,hlr0) ->
case AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
u AVL e
ll0 Int#
hll0 AVL e
l1 Int#
hl1 of
UBT2(l,hl) -> case AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
u AVL e
lr0 Int#
hlr0 AVL e
rl1 Int#
hrl1 of
UBT2(m,hm) -> case AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
u AVL e
r0 Int#
hr0 AVL e
rr1 Int#
hrr1 of
UBT2(r,hr) -> case AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
forall e. AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
spliceH AVL e
l Int#
hl e
e1_ AVL e
m Int#
hm of
UBT2(t,ht) -> AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
forall e. AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
spliceH AVL e
t Int#
ht e
e0_ AVL e
r Int#
hr
forkL :: e -> AVL e -> Int# -> (# AVL e, Int#, e, AVL e, Int# #)
forkL e
e0 AVL e
t1 Int#
ht1 = AVL e -> Int# -> (# AVL e, Int#, e, AVL e, Int# #)
forkL_ AVL e
t1 Int#
ht1 where
forkL_ :: AVL e -> Int# -> (# AVL e, Int#, e, AVL e, Int# #)
forkL_ AVL e
E Int#
_ = UBT5(E, L(0), e0, E, L(0))
forkL_ (N AVL e
l e
e AVL e
r) Int#
h = AVL e
-> Int# -> e -> AVL e -> Int# -> (# AVL e, Int#, e, AVL e, Int# #)
forkL__ AVL e
l DECINT2(h) e r DECINT1(h)
forkL_ (Z AVL e
l e
e AVL e
r) Int#
h = AVL e
-> Int# -> e -> AVL e -> Int# -> (# AVL e, Int#, e, AVL e, Int# #)
forkL__ AVL e
l DECINT1(h) e r DECINT1(h)
forkL_ (P AVL e
l e
e AVL e
r) Int#
h = AVL e
-> Int# -> e -> AVL e -> Int# -> (# AVL e, Int#, e, AVL e, Int# #)
forkL__ AVL e
l DECINT1(h) e r DECINT2(h)
forkL__ :: AVL e
-> Int# -> e -> AVL e -> Int# -> (# AVL e, Int#, e, AVL e, Int# #)
forkL__ AVL e
l Int#
hl e
e AVL e
r Int#
hr = case e -> e -> COrdering e
c e
e0 e
e of
COrdering e
Lt -> case AVL e -> Int# -> (# AVL e, Int#, e, AVL e, Int# #)
forkL_ AVL e
l Int#
hl of
UBT5(l0,hl0,e0_,l1,hl1) -> case AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
forall e. AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
spliceH AVL e
l1 Int#
hl1 e
e AVL e
r Int#
hr of
UBT2(l1_,hl1_) -> UBT5(l0,hl0,e0_,l1_,hl1_)
Eq e
e0_ -> UBT5(l,hl,e0_,r,hr)
COrdering e
Gt -> case AVL e -> Int# -> (# AVL e, Int#, e, AVL e, Int# #)
forkL_ AVL e
r Int#
hr of
UBT5(l0,hl0,e0_,l1,hl1) -> case AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
forall e. AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
spliceH AVL e
l Int#
hl e
e AVL e
l0 Int#
hl0 of
UBT2(l0_,hl0_) -> UBT5(l0_,hl0_,e0_,l1,hl1)
forkR :: AVL e -> Int# -> e -> (# AVL e, Int#, e, AVL e, Int# #)
forkR AVL e
t0 Int#
ht0 e
e1 = AVL e -> Int# -> (# AVL e, Int#, e, AVL e, Int# #)
forkR_ AVL e
t0 Int#
ht0 where
forkR_ :: AVL e -> Int# -> (# AVL e, Int#, e, AVL e, Int# #)
forkR_ AVL e
E Int#
_ = UBT5(E, L(0), e1, E, L(0))
forkR_ (N AVL e
l e
e AVL e
r) Int#
h = AVL e
-> Int# -> e -> AVL e -> Int# -> (# AVL e, Int#, e, AVL e, Int# #)
forkR__ AVL e
l DECINT2(h) e r DECINT1(h)
forkR_ (Z AVL e
l e
e AVL e
r) Int#
h = AVL e
-> Int# -> e -> AVL e -> Int# -> (# AVL e, Int#, e, AVL e, Int# #)
forkR__ AVL e
l DECINT1(h) e r DECINT1(h)
forkR_ (P AVL e
l e
e AVL e
r) Int#
h = AVL e
-> Int# -> e -> AVL e -> Int# -> (# AVL e, Int#, e, AVL e, Int# #)
forkR__ AVL e
l DECINT1(h) e r DECINT2(h)
forkR__ :: AVL e
-> Int# -> e -> AVL e -> Int# -> (# AVL e, Int#, e, AVL e, Int# #)
forkR__ AVL e
l Int#
hl e
e AVL e
r Int#
hr = case e -> e -> COrdering e
c e
e e
e1 of
COrdering e
Lt -> case AVL e -> Int# -> (# AVL e, Int#, e, AVL e, Int# #)
forkR_ AVL e
r Int#
hr of
UBT5(l0,hl0,e1_,l1,hl1) -> case AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
forall e. AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
spliceH AVL e
l Int#
hl e
e AVL e
l0 Int#
hl0 of
UBT2(l0_,hl0_) -> UBT5(l0_,hl0_,e1_,l1,hl1)
Eq e
e1_ -> UBT5(l,hl,e1_,r,hr)
COrdering e
Gt -> case AVL e -> Int# -> (# AVL e, Int#, e, AVL e, Int# #)
forkR_ AVL e
l Int#
hl of
UBT5(l0,hl0,e1_,l1,hl1) -> case AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
forall e. AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
spliceH AVL e
l1 Int#
hl1 e
e AVL e
r Int#
hr of
UBT2(l1_,hl1_) -> UBT5(l0,hl0,e1_,l1_,hl1_)
unionMaybeH :: (e -> e -> COrdering (Maybe e)) -> AVL e -> UINT -> AVL e -> UINT -> UBT2(AVL e,UINT)
unionMaybeH :: forall e.
(e -> e -> COrdering (Maybe e))
-> AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
unionMaybeH e -> e -> COrdering (Maybe e)
c = AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
u where
u :: AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
u AVL e
E Int#
_ AVL e
t1 Int#
h1 = UBT2(t1,h1)
u AVL e
t0 Int#
h0 AVL e
E Int#
_ = UBT2(t0,h0)
u (N AVL e
l0 e
e0 AVL e
r0) Int#
h0 (N AVL e
l1 e
e1 AVL e
r1) Int#
h1 = AVL e
-> Int#
-> e
-> AVL e
-> Int#
-> AVL e
-> Int#
-> e
-> AVL e
-> Int#
-> (# AVL e, Int# #)
u_ AVL e
l0 DECINT2(h0) e0 r0 DECINT1(h0) l1 DECINT2(h1) AVL e
e1 r1 DECINT1(h1)
u (N AVL e
l0 e
e0 AVL e
r0) Int#
h0 (Z AVL e
l1 e
e1 AVL e
r1) Int#
h1 = AVL e
-> Int#
-> e
-> AVL e
-> Int#
-> AVL e
-> Int#
-> e
-> AVL e
-> Int#
-> (# AVL e, Int# #)
u_ AVL e
l0 DECINT2(h0) e0 r0 DECINT1(h0) l1 DECINT1(h1) AVL e
e1 r1 DECINT1(h1)
u (N AVL e
l0 e
e0 AVL e
r0) Int#
h0 (P AVL e
l1 e
e1 AVL e
r1) Int#
h1 = AVL e
-> Int#
-> e
-> AVL e
-> Int#
-> AVL e
-> Int#
-> e
-> AVL e
-> Int#
-> (# AVL e, Int# #)
u_ AVL e
l0 DECINT2(h0) e0 r0 DECINT1(h0) l1 DECINT1(h1) AVL e
e1 r1 DECINT2(h1)
u (Z AVL e
l0 e
e0 AVL e
r0) Int#
h0 (N AVL e
l1 e
e1 AVL e
r1) Int#
h1 = AVL e
-> Int#
-> e
-> AVL e
-> Int#
-> AVL e
-> Int#
-> e
-> AVL e
-> Int#
-> (# AVL e, Int# #)
u_ AVL e
l0 DECINT1(h0) e0 r0 DECINT1(h0) l1 DECINT2(h1) AVL e
e1 r1 DECINT1(h1)
u (Z AVL e
l0 e
e0 AVL e
r0) Int#
h0 (Z AVL e
l1 e
e1 AVL e
r1) Int#
h1 = AVL e
-> Int#
-> e
-> AVL e
-> Int#
-> AVL e
-> Int#
-> e
-> AVL e
-> Int#
-> (# AVL e, Int# #)
u_ AVL e
l0 DECINT1(h0) e0 r0 DECINT1(h0) l1 DECINT1(h1) AVL e
e1 r1 DECINT1(h1)
u (Z AVL e
l0 e
e0 AVL e
r0) Int#
h0 (P AVL e
l1 e
e1 AVL e
r1) Int#
h1 = AVL e
-> Int#
-> e
-> AVL e
-> Int#
-> AVL e
-> Int#
-> e
-> AVL e
-> Int#
-> (# AVL e, Int# #)
u_ AVL e
l0 DECINT1(h0) e0 r0 DECINT1(h0) l1 DECINT1(h1) AVL e
e1 r1 DECINT2(h1)
u (P AVL e
l0 e
e0 AVL e
r0) Int#
h0 (N AVL e
l1 e
e1 AVL e
r1) Int#
h1 = AVL e
-> Int#
-> e
-> AVL e
-> Int#
-> AVL e
-> Int#
-> e
-> AVL e
-> Int#
-> (# AVL e, Int# #)
u_ AVL e
l0 DECINT1(h0) e0 r0 DECINT2(h0) l1 DECINT2(h1) AVL e
e1 r1 DECINT1(h1)
u (P AVL e
l0 e
e0 AVL e
r0) Int#
h0 (Z AVL e
l1 e
e1 AVL e
r1) Int#
h1 = AVL e
-> Int#
-> e
-> AVL e
-> Int#
-> AVL e
-> Int#
-> e
-> AVL e
-> Int#
-> (# AVL e, Int# #)
u_ AVL e
l0 DECINT1(h0) e0 r0 DECINT2(h0) l1 DECINT1(h1) AVL e
e1 r1 DECINT1(h1)
u (P AVL e
l0 e
e0 AVL e
r0) Int#
h0 (P AVL e
l1 e
e1 AVL e
r1) Int#
h1 = AVL e
-> Int#
-> e
-> AVL e
-> Int#
-> AVL e
-> Int#
-> e
-> AVL e
-> Int#
-> (# AVL e, Int# #)
u_ AVL e
l0 DECINT1(h0) e0 r0 DECINT2(h0) l1 DECINT1(h1) AVL e
e1 r1 DECINT2(h1)
u_ :: AVL e
-> Int#
-> e
-> AVL e
-> Int#
-> AVL e
-> Int#
-> e
-> AVL e
-> Int#
-> (# AVL e, Int# #)
u_ AVL e
l0 Int#
hl0 e
e0 AVL e
r0 Int#
hr0 AVL e
l1 Int#
hl1 e
e1 AVL e
r1 Int#
hr1 =
case e -> e -> COrdering (Maybe e)
c e
e0 e
e1 of
COrdering (Maybe e)
Lt -> case AVL e -> Int# -> e -> (# AVL e, Int#, Maybe e, AVL e, Int# #)
forkR AVL e
r0 Int#
hr0 e
e1 of
UBT5(rl0,hrl0,mbe1_,rr0,hrr0) -> case e -> AVL e -> Int# -> (# AVL e, Int#, Maybe e, AVL e, Int# #)
forkL e
e0 AVL e
l1 Int#
hl1 of
UBT5(ll1,hll1,mbe0_,lr1,hlr1) ->
case AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
u AVL e
l0 Int#
hl0 AVL e
ll1 Int#
hll1 of
UBT2(l,hl) -> case AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
u AVL e
rl0 Int#
hrl0 AVL e
lr1 Int#
hlr1 of
UBT2(m,hm) -> case AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
u AVL e
rr0 Int#
hrr0 AVL e
r1 Int#
hr1 of
UBT2(r,hr) -> case (case Maybe e
mbe1_ of
Just e
e1_ -> AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
forall e. AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
spliceH AVL e
m Int#
hm e
e1_ AVL e
r Int#
hr
Maybe e
Nothing -> AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
forall e. AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
joinH AVL e
m Int#
hm AVL e
r Int#
hr
) of
UBT2(t,ht) -> case Maybe e
mbe0_ of
Just e
e0_ -> AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
forall e. AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
spliceH AVL e
l Int#
hl e
e0_ AVL e
t Int#
ht
Maybe e
Nothing -> AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
forall e. AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
joinH AVL e
l Int#
hl AVL e
t Int#
ht
Eq Maybe e
mbe -> case AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
u AVL e
l0 Int#
hl0 AVL e
l1 Int#
hl1 of
UBT2(l,hl) -> case AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
u AVL e
r0 Int#
hr0 AVL e
r1 Int#
hr1 of
UBT2(r,hr) -> case Maybe e
mbe of
Just e
e -> AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
forall e. AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
spliceH AVL e
l Int#
hl e
e AVL e
r Int#
hr
Maybe e
Nothing -> AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
forall e. AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
joinH AVL e
l Int#
hl AVL e
r Int#
hr
COrdering (Maybe e)
Gt -> case e -> AVL e -> Int# -> (# AVL e, Int#, Maybe e, AVL e, Int# #)
forkL e
e0 AVL e
r1 Int#
hr1 of
UBT5(rl1,hrl1,mbe0_,rr1,hrr1) -> case AVL e -> Int# -> e -> (# AVL e, Int#, Maybe e, AVL e, Int# #)
forkR AVL e
l0 Int#
hl0 e
e1 of
UBT5(ll0,hll0,mbe1_,lr0,hlr0) ->
case AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
u AVL e
ll0 Int#
hll0 AVL e
l1 Int#
hl1 of
UBT2(l,hl) -> case AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
u AVL e
lr0 Int#
hlr0 AVL e
rl1 Int#
hrl1 of
UBT2(m,hm) -> case AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
u AVL e
r0 Int#
hr0 AVL e
rr1 Int#
hrr1 of
UBT2(r,hr) -> case (case Maybe e
mbe1_ of
Just e
e1_ -> AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
forall e. AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
spliceH AVL e
l Int#
hl e
e1_ AVL e
m Int#
hm
Maybe e
Nothing -> AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
forall e. AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
joinH AVL e
l Int#
hl AVL e
m Int#
hm
) of
UBT2(t,ht) -> case Maybe e
mbe0_ of
Just e
e0_ -> AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
forall e. AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
spliceH AVL e
t Int#
ht e
e0_ AVL e
r Int#
hr
Maybe e
Nothing -> AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
forall e. AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
joinH AVL e
t Int#
ht AVL e
r Int#
hr
forkL :: e -> AVL e -> Int# -> (# AVL e, Int#, Maybe e, AVL e, Int# #)
forkL e
e0 AVL e
t1 Int#
ht1 = AVL e -> Int# -> (# AVL e, Int#, Maybe e, AVL e, Int# #)
forkL_ AVL e
t1 Int#
ht1 where
forkL_ :: AVL e -> Int# -> (# AVL e, Int#, Maybe e, AVL e, Int# #)
forkL_ AVL e
E Int#
_ = UBT5(E, L(0), Just e0, E, L(0))
forkL_ (N AVL e
l e
e AVL e
r) Int#
h = AVL e
-> Int#
-> e
-> AVL e
-> Int#
-> (# AVL e, Int#, Maybe e, AVL e, Int# #)
forkL__ AVL e
l DECINT2(h) e r DECINT1(h)
forkL_ (Z AVL e
l e
e AVL e
r) Int#
h = AVL e
-> Int#
-> e
-> AVL e
-> Int#
-> (# AVL e, Int#, Maybe e, AVL e, Int# #)
forkL__ AVL e
l DECINT1(h) e r DECINT1(h)
forkL_ (P AVL e
l e
e AVL e
r) Int#
h = AVL e
-> Int#
-> e
-> AVL e
-> Int#
-> (# AVL e, Int#, Maybe e, AVL e, Int# #)
forkL__ AVL e
l DECINT1(h) e r DECINT2(h)
forkL__ :: AVL e
-> Int#
-> e
-> AVL e
-> Int#
-> (# AVL e, Int#, Maybe e, AVL e, Int# #)
forkL__ AVL e
l Int#
hl e
e AVL e
r Int#
hr = case e -> e -> COrdering (Maybe e)
c e
e0 e
e of
COrdering (Maybe e)
Lt -> case AVL e -> Int# -> (# AVL e, Int#, Maybe e, AVL e, Int# #)
forkL_ AVL e
l Int#
hl of
UBT5(l0,hl0,mbe0_,l1,hl1) -> case AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
forall e. AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
spliceH AVL e
l1 Int#
hl1 e
e AVL e
r Int#
hr of
UBT2(l1_,hl1_) -> UBT5(l0,hl0,mbe0_,l1_,hl1_)
Eq Maybe e
mbe0_ -> UBT5(l,hl,mbe0_,r,hr)
COrdering (Maybe e)
Gt -> case AVL e -> Int# -> (# AVL e, Int#, Maybe e, AVL e, Int# #)
forkL_ AVL e
r Int#
hr of
UBT5(l0,hl0,mbe0_,l1,hl1) -> case AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
forall e. AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
spliceH AVL e
l Int#
hl e
e AVL e
l0 Int#
hl0 of
UBT2(l0_,hl0_) -> UBT5(l0_,hl0_,mbe0_,l1,hl1)
forkR :: AVL e -> Int# -> e -> (# AVL e, Int#, Maybe e, AVL e, Int# #)
forkR AVL e
t0 Int#
ht0 e
e1 = AVL e -> Int# -> (# AVL e, Int#, Maybe e, AVL e, Int# #)
forkR_ AVL e
t0 Int#
ht0 where
forkR_ :: AVL e -> Int# -> (# AVL e, Int#, Maybe e, AVL e, Int# #)
forkR_ AVL e
E Int#
_ = UBT5(E, L(0), Just e1, E, L(0))
forkR_ (N AVL e
l e
e AVL e
r) Int#
h = AVL e
-> Int#
-> e
-> AVL e
-> Int#
-> (# AVL e, Int#, Maybe e, AVL e, Int# #)
forkR__ AVL e
l DECINT2(h) e r DECINT1(h)
forkR_ (Z AVL e
l e
e AVL e
r) Int#
h = AVL e
-> Int#
-> e
-> AVL e
-> Int#
-> (# AVL e, Int#, Maybe e, AVL e, Int# #)
forkR__ AVL e
l DECINT1(h) e r DECINT1(h)
forkR_ (P AVL e
l e
e AVL e
r) Int#
h = AVL e
-> Int#
-> e
-> AVL e
-> Int#
-> (# AVL e, Int#, Maybe e, AVL e, Int# #)
forkR__ AVL e
l DECINT1(h) e r DECINT2(h)
forkR__ :: AVL e
-> Int#
-> e
-> AVL e
-> Int#
-> (# AVL e, Int#, Maybe e, AVL e, Int# #)
forkR__ AVL e
l Int#
hl e
e AVL e
r Int#
hr = case e -> e -> COrdering (Maybe e)
c e
e e
e1 of
COrdering (Maybe e)
Lt -> case AVL e -> Int# -> (# AVL e, Int#, Maybe e, AVL e, Int# #)
forkR_ AVL e
r Int#
hr of
UBT5(l0,hl0,mbe1_,l1,hl1) -> case AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
forall e. AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
spliceH AVL e
l Int#
hl e
e AVL e
l0 Int#
hl0 of
UBT2(l0_,hl0_) -> UBT5(l0_,hl0_,mbe1_,l1,hl1)
Eq Maybe e
mbe1_ -> UBT5(l,hl,mbe1_,r,hr)
COrdering (Maybe e)
Gt -> case AVL e -> Int# -> (# AVL e, Int#, Maybe e, AVL e, Int# #)
forkR_ AVL e
l Int#
hl of
UBT5(l0,hl0,mbe1_,l1,hl1) -> case AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
forall e. AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
spliceH AVL e
l1 Int#
hl1 e
e AVL e
r Int#
hr of
UBT2(l1_,hl1_) -> UBT5(l0,hl0,mbe1_,l1_,hl1_)
disjointUnionH :: (e -> e -> Ordering) -> AVL e -> UINT -> AVL e -> UINT -> UBT2(AVL e,UINT)
disjointUnionH :: forall e.
(e -> e -> Ordering)
-> AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
disjointUnionH e -> e -> Ordering
c = AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
u where
u :: AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
u AVL e
E Int#
_ AVL e
t1 Int#
h1 = UBT2(t1,h1)
u AVL e
t0 Int#
h0 AVL e
E Int#
_ = UBT2(t0,h0)
u (N AVL e
l0 e
e0 AVL e
r0) Int#
h0 (N AVL e
l1 e
e1 AVL e
r1) Int#
h1 = AVL e
-> Int#
-> e
-> AVL e
-> Int#
-> AVL e
-> Int#
-> e
-> AVL e
-> Int#
-> (# AVL e, Int# #)
u_ AVL e
l0 DECINT2(h0) e0 r0 DECINT1(h0) l1 DECINT2(h1) AVL e
e1 r1 DECINT1(h1)
u (N AVL e
l0 e
e0 AVL e
r0) Int#
h0 (Z AVL e
l1 e
e1 AVL e
r1) Int#
h1 = AVL e
-> Int#
-> e
-> AVL e
-> Int#
-> AVL e
-> Int#
-> e
-> AVL e
-> Int#
-> (# AVL e, Int# #)
u_ AVL e
l0 DECINT2(h0) e0 r0 DECINT1(h0) l1 DECINT1(h1) AVL e
e1 r1 DECINT1(h1)
u (N AVL e
l0 e
e0 AVL e
r0) Int#
h0 (P AVL e
l1 e
e1 AVL e
r1) Int#
h1 = AVL e
-> Int#
-> e
-> AVL e
-> Int#
-> AVL e
-> Int#
-> e
-> AVL e
-> Int#
-> (# AVL e, Int# #)
u_ AVL e
l0 DECINT2(h0) e0 r0 DECINT1(h0) l1 DECINT1(h1) AVL e
e1 r1 DECINT2(h1)
u (Z AVL e
l0 e
e0 AVL e
r0) Int#
h0 (N AVL e
l1 e
e1 AVL e
r1) Int#
h1 = AVL e
-> Int#
-> e
-> AVL e
-> Int#
-> AVL e
-> Int#
-> e
-> AVL e
-> Int#
-> (# AVL e, Int# #)
u_ AVL e
l0 DECINT1(h0) e0 r0 DECINT1(h0) l1 DECINT2(h1) AVL e
e1 r1 DECINT1(h1)
u (Z AVL e
l0 e
e0 AVL e
r0) Int#
h0 (Z AVL e
l1 e
e1 AVL e
r1) Int#
h1 = AVL e
-> Int#
-> e
-> AVL e
-> Int#
-> AVL e
-> Int#
-> e
-> AVL e
-> Int#
-> (# AVL e, Int# #)
u_ AVL e
l0 DECINT1(h0) e0 r0 DECINT1(h0) l1 DECINT1(h1) AVL e
e1 r1 DECINT1(h1)
u (Z AVL e
l0 e
e0 AVL e
r0) Int#
h0 (P AVL e
l1 e
e1 AVL e
r1) Int#
h1 = AVL e
-> Int#
-> e
-> AVL e
-> Int#
-> AVL e
-> Int#
-> e
-> AVL e
-> Int#
-> (# AVL e, Int# #)
u_ AVL e
l0 DECINT1(h0) e0 r0 DECINT1(h0) l1 DECINT1(h1) AVL e
e1 r1 DECINT2(h1)
u (P AVL e
l0 e
e0 AVL e
r0) Int#
h0 (N AVL e
l1 e
e1 AVL e
r1) Int#
h1 = AVL e
-> Int#
-> e
-> AVL e
-> Int#
-> AVL e
-> Int#
-> e
-> AVL e
-> Int#
-> (# AVL e, Int# #)
u_ AVL e
l0 DECINT1(h0) e0 r0 DECINT2(h0) l1 DECINT2(h1) AVL e
e1 r1 DECINT1(h1)
u (P AVL e
l0 e
e0 AVL e
r0) Int#
h0 (Z AVL e
l1 e
e1 AVL e
r1) Int#
h1 = AVL e
-> Int#
-> e
-> AVL e
-> Int#
-> AVL e
-> Int#
-> e
-> AVL e
-> Int#
-> (# AVL e, Int# #)
u_ AVL e
l0 DECINT1(h0) e0 r0 DECINT2(h0) l1 DECINT1(h1) AVL e
e1 r1 DECINT1(h1)
u (P AVL e
l0 e
e0 AVL e
r0) Int#
h0 (P AVL e
l1 e
e1 AVL e
r1) Int#
h1 = AVL e
-> Int#
-> e
-> AVL e
-> Int#
-> AVL e
-> Int#
-> e
-> AVL e
-> Int#
-> (# AVL e, Int# #)
u_ AVL e
l0 DECINT1(h0) e0 r0 DECINT2(h0) l1 DECINT1(h1) AVL e
e1 r1 DECINT2(h1)
u_ :: AVL e
-> Int#
-> e
-> AVL e
-> Int#
-> AVL e
-> Int#
-> e
-> AVL e
-> Int#
-> (# AVL e, Int# #)
u_ AVL e
l0 Int#
hl0 e
e0 AVL e
r0 Int#
hr0 AVL e
l1 Int#
hl1 e
e1 AVL e
r1 Int#
hr1 =
case e -> e -> Ordering
c e
e0 e
e1 of
Ordering
LT -> case e -> AVL e -> Int# -> (# AVL e, Int#, AVL e, Int# #)
fork e
e1 AVL e
r0 Int#
hr0 of
UBT4(rl0,hrl0,rr0,hrr0) -> case e -> AVL e -> Int# -> (# AVL e, Int#, AVL e, Int# #)
fork e
e0 AVL e
l1 Int#
hl1 of
UBT4(ll1,hll1,lr1,hlr1) ->
case AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
u AVL e
l0 Int#
hl0 AVL e
ll1 Int#
hll1 of
UBT2(l,hl) -> case AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
u AVL e
rl0 Int#
hrl0 AVL e
lr1 Int#
hlr1 of
UBT2(m,hm) -> case AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
u AVL e
rr0 Int#
hrr0 AVL e
r1 Int#
hr1 of
UBT2(r,hr) -> case AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
forall e. AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
spliceH AVL e
m Int#
hm e
e1 AVL e
r Int#
hr of
UBT2(t,ht) -> AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
forall e. AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
spliceH AVL e
l Int#
hl e
e0 AVL e
t Int#
ht
Ordering
EQ -> [Char] -> Any
forall a. HasCallStack => [Char] -> a
error [Char]
"disjointUnionH: Trees intersect" Any -> (# AVL e, Int# #) -> (# AVL e, Int# #)
forall a b. a -> b -> b
`seq` UBT2(E,L(0))
Ordering
GT -> case e -> AVL e -> Int# -> (# AVL e, Int#, AVL e, Int# #)
fork e
e0 AVL e
r1 Int#
hr1 of
UBT4(rl1,hrl1,rr1,hrr1) -> case e -> AVL e -> Int# -> (# AVL e, Int#, AVL e, Int# #)
fork e
e1 AVL e
l0 Int#
hl0 of
UBT4(ll0,hll0,lr0,hlr0) ->
case AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
u AVL e
ll0 Int#
hll0 AVL e
l1 Int#
hl1 of
UBT2(l,hl) -> case AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
u AVL e
lr0 Int#
hlr0 AVL e
rl1 Int#
hrl1 of
UBT2(m,hm) -> case AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
u AVL e
r0 Int#
hr0 AVL e
rr1 Int#
hrr1 of
UBT2(r,hr) -> case AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
forall e. AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
spliceH AVL e
l Int#
hl e
e1 AVL e
m Int#
hm of
UBT2(t,ht) -> AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
forall e. AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
spliceH AVL e
t Int#
ht e
e0 AVL e
r Int#
hr
fork :: e -> AVL e -> Int# -> (# AVL e, Int#, AVL e, Int# #)
fork e
e0 AVL e
t1 Int#
ht1 = AVL e -> Int# -> (# AVL e, Int#, AVL e, Int# #)
fork_ AVL e
t1 Int#
ht1 where
fork_ :: AVL e -> Int# -> (# AVL e, Int#, AVL e, Int# #)
fork_ AVL e
E Int#
_ = UBT4(E, L(AVL e
forall e. AVL e
0), E, L(0))
fork_ (N AVL e
l e
e AVL e
r) Int#
h = AVL e
-> Int# -> e -> AVL e -> Int# -> (# AVL e, Int#, AVL e, Int# #)
fork__ AVL e
l DECINT2(h) e r DECINT1(h)
fork_ (Z AVL e
l e
e AVL e
r) Int#
h = AVL e
-> Int# -> e -> AVL e -> Int# -> (# AVL e, Int#, AVL e, Int# #)
fork__ AVL e
l DECINT1(h) e r DECINT1(h)
fork_ (P AVL e
l e
e AVL e
r) Int#
h = AVL e
-> Int# -> e -> AVL e -> Int# -> (# AVL e, Int#, AVL e, Int# #)
fork__ AVL e
l DECINT1(h) e r DECINT2(h)
fork__ :: AVL e
-> Int# -> e -> AVL e -> Int# -> (# AVL e, Int#, AVL e, Int# #)
fork__ AVL e
l Int#
hl e
e AVL e
r Int#
hr = case e -> e -> Ordering
c e
e0 e
e of
Ordering
LT -> case AVL e -> Int# -> (# AVL e, Int#, AVL e, Int# #)
fork_ AVL e
l Int#
hl of
UBT4(l0,hl0,l1,hl1) -> case AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
forall e. AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
spliceH AVL e
l1 Int#
hl1 e
e AVL e
r Int#
hr of
UBT2(l1_,hl1_) -> UBT4(l0,hl0,l1_,hl1_)
Ordering
EQ -> [Char] -> Any
forall a. HasCallStack => [Char] -> a
error [Char]
"disjointUnionH: Trees intersect" Any
-> (# AVL e, Int#, AVL e, Int# #) -> (# AVL e, Int#, AVL e, Int# #)
forall a b. a -> b -> b
`seq` UBT4(E, L(AVL e
forall e. AVL e
0), E, L(0))
Ordering
GT -> case AVL e -> Int# -> (# AVL e, Int#, AVL e, Int# #)
fork_ AVL e
r Int#
hr of
UBT4(l0,hl0,l1,hl1) -> case AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
forall e. AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
spliceH AVL e
l Int#
hl e
e AVL e
l0 Int#
hl0 of
UBT2(l0_,hl0_) -> UBT4(l0_,hl0_,l1,hl1)
intersectionH :: (a -> b -> COrdering c) -> AVL a -> AVL b -> UBT2(AVL c,UINT)
intersectionH :: forall a b c.
(a -> b -> COrdering c) -> AVL a -> AVL b -> (# AVL c, Int# #)
intersectionH a -> b -> COrdering c
cmp = AVL a -> AVL b -> (# AVL c, Int# #)
i where
i :: AVL a -> AVL b -> (# AVL c, Int# #)
i AVL a
E AVL b
_ = UBT2(E,L(0))
i AVL a
_ AVL b
E = UBT2(E,L(0))
i (N AVL a
l0 a
e0 AVL a
r0) (N AVL b
l1 b
e1 AVL b
r1) = AVL a -> a -> AVL a -> AVL b -> b -> AVL b -> (# AVL c, Int# #)
i_ AVL a
l0 a
e0 AVL a
r0 AVL b
l1 b
e1 AVL b
r1
i (N AVL a
l0 a
e0 AVL a
r0) (Z AVL b
l1 b
e1 AVL b
r1) = AVL a -> a -> AVL a -> AVL b -> b -> AVL b -> (# AVL c, Int# #)
i_ AVL a
l0 a
e0 AVL a
r0 AVL b
l1 b
e1 AVL b
r1
i (N AVL a
l0 a
e0 AVL a
r0) (P AVL b
l1 b
e1 AVL b
r1) = AVL a -> a -> AVL a -> AVL b -> b -> AVL b -> (# AVL c, Int# #)
i_ AVL a
l0 a
e0 AVL a
r0 AVL b
l1 b
e1 AVL b
r1
i (Z AVL a
l0 a
e0 AVL a
r0) (N AVL b
l1 b
e1 AVL b
r1) = AVL a -> a -> AVL a -> AVL b -> b -> AVL b -> (# AVL c, Int# #)
i_ AVL a
l0 a
e0 AVL a
r0 AVL b
l1 b
e1 AVL b
r1
i (Z AVL a
l0 a
e0 AVL a
r0) (Z AVL b
l1 b
e1 AVL b
r1) = AVL a -> a -> AVL a -> AVL b -> b -> AVL b -> (# AVL c, Int# #)
i_ AVL a
l0 a
e0 AVL a
r0 AVL b
l1 b
e1 AVL b
r1
i (Z AVL a
l0 a
e0 AVL a
r0) (P AVL b
l1 b
e1 AVL b
r1) = AVL a -> a -> AVL a -> AVL b -> b -> AVL b -> (# AVL c, Int# #)
i_ AVL a
l0 a
e0 AVL a
r0 AVL b
l1 b
e1 AVL b
r1
i (P AVL a
l0 a
e0 AVL a
r0) (N AVL b
l1 b
e1 AVL b
r1) = AVL a -> a -> AVL a -> AVL b -> b -> AVL b -> (# AVL c, Int# #)
i_ AVL a
l0 a
e0 AVL a
r0 AVL b
l1 b
e1 AVL b
r1
i (P AVL a
l0 a
e0 AVL a
r0) (Z AVL b
l1 b
e1 AVL b
r1) = AVL a -> a -> AVL a -> AVL b -> b -> AVL b -> (# AVL c, Int# #)
i_ AVL a
l0 a
e0 AVL a
r0 AVL b
l1 b
e1 AVL b
r1
i (P AVL a
l0 a
e0 AVL a
r0) (P AVL b
l1 b
e1 AVL b
r1) = AVL a -> a -> AVL a -> AVL b -> b -> AVL b -> (# AVL c, Int# #)
i_ AVL a
l0 a
e0 AVL a
r0 AVL b
l1 b
e1 AVL b
r1
i_ :: AVL a -> a -> AVL a -> AVL b -> b -> AVL b -> (# AVL c, Int# #)
i_ AVL a
l0 a
e0 AVL a
r0 AVL b
l1 b
e1 AVL b
r1 =
case a -> b -> COrdering c
cmp a
e0 b
e1 of
COrdering c
Lt -> case AVL a -> b -> (# AVL a, Int#, Maybe c, AVL a, Int# #)
forkR AVL a
r0 b
e1 of
UBT5(rl0,_,mbc1,rr0,_) -> case a -> AVL b -> (# AVL b, Int#, Maybe c, AVL b, Int# #)
forkL a
e0 AVL b
l1 of
UBT5(ll1,_,mbc0,lr1,_) ->
case AVL a -> AVL b -> (# AVL c, Int# #)
i AVL a
rr0 AVL b
r1 of
UBT2(r,hr) -> case AVL a -> AVL b -> (# AVL c, Int# #)
i AVL a
rl0 AVL b
lr1 of
UBT2(m,hm) -> case AVL a -> AVL b -> (# AVL c, Int# #)
i AVL a
l0 AVL b
ll1 of
UBT2(l,hl) -> case (case Maybe c
mbc1 of
Just c
c1 -> AVL c -> Int# -> c -> AVL c -> Int# -> (# AVL c, Int# #)
forall e. AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
spliceH AVL c
m Int#
hm c
c1 AVL c
r Int#
hr
Maybe c
Nothing -> AVL c -> Int# -> AVL c -> Int# -> (# AVL c, Int# #)
forall e. AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
joinH AVL c
m Int#
hm AVL c
r Int#
hr
) of
UBT2(t,ht) -> case Maybe c
mbc0 of
Just c
c0 -> AVL c -> Int# -> c -> AVL c -> Int# -> (# AVL c, Int# #)
forall e. AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
spliceH AVL c
l Int#
hl c
c0 AVL c
t Int#
ht
Maybe c
Nothing -> AVL c -> Int# -> AVL c -> Int# -> (# AVL c, Int# #)
forall e. AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
joinH AVL c
l Int#
hl AVL c
t Int#
ht
Eq c
c -> case AVL a -> AVL b -> (# AVL c, Int# #)
i AVL a
l0 AVL b
l1 of
UBT2(l,hl) -> case AVL a -> AVL b -> (# AVL c, Int# #)
i AVL a
r0 AVL b
r1 of
UBT2(r,hr) -> AVL c -> Int# -> c -> AVL c -> Int# -> (# AVL c, Int# #)
forall e. AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
spliceH AVL c
l Int#
hl c
c AVL c
r Int#
hr
COrdering c
Gt -> case a -> AVL b -> (# AVL b, Int#, Maybe c, AVL b, Int# #)
forkL a
e0 AVL b
r1 of
UBT5(rl1,_,mbc0,rr1,_) -> case AVL a -> b -> (# AVL a, Int#, Maybe c, AVL a, Int# #)
forkR AVL a
l0 b
e1 of
UBT5(ll0,_,mbc1,lr0,_) ->
case AVL a -> AVL b -> (# AVL c, Int# #)
i AVL a
r0 AVL b
rr1 of
UBT2(r,hr) -> case AVL a -> AVL b -> (# AVL c, Int# #)
i AVL a
lr0 AVL b
rl1 of
UBT2(m,hm) -> case AVL a -> AVL b -> (# AVL c, Int# #)
i AVL a
ll0 AVL b
l1 of
UBT2(l,hl) -> case (case Maybe c
mbc0 of
Just c
c0 -> AVL c -> Int# -> c -> AVL c -> Int# -> (# AVL c, Int# #)
forall e. AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
spliceH AVL c
m Int#
hm c
c0 AVL c
r Int#
hr
Maybe c
Nothing -> AVL c -> Int# -> AVL c -> Int# -> (# AVL c, Int# #)
forall e. AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
joinH AVL c
m Int#
hm AVL c
r Int#
hr
) of
UBT2(t,ht) -> case Maybe c
mbc1 of
Just c
c1 -> AVL c -> Int# -> c -> AVL c -> Int# -> (# AVL c, Int# #)
forall e. AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
spliceH AVL c
l Int#
hl c
c1 AVL c
t Int#
ht
Maybe c
Nothing -> AVL c -> Int# -> AVL c -> Int# -> (# AVL c, Int# #)
forall e. AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
joinH AVL c
l Int#
hl AVL c
t Int#
ht
forkL :: a -> AVL b -> (# AVL b, Int#, Maybe c, AVL b, Int# #)
forkL a
e0 AVL b
t1 = AVL b -> Int# -> (# AVL b, Int#, Maybe c, AVL b, Int# #)
forkL_ AVL b
t1 L(0) where
forkL_ :: AVL b -> Int# -> (# AVL b, Int#, Maybe c, AVL b, Int# #)
forkL_ AVL b
E Int#
h = UBT5(Int#
E,h,Nothing,Int#
E,h)
forkL_ (N AVL b
l b
e AVL b
r) Int#
h = AVL b
-> Int#
-> b
-> AVL b
-> Int#
-> (# AVL b, Int#, Maybe c, AVL b, Int# #)
forkL__ AVL b
l DECINT2(h) e r DECINT1(h)
forkL_ (Z AVL b
l b
e AVL b
r) Int#
h = AVL b
-> Int#
-> b
-> AVL b
-> Int#
-> (# AVL b, Int#, Maybe c, AVL b, Int# #)
forkL__ AVL b
l DECINT1(h) e r DECINT1(h)
forkL_ (P AVL b
l b
e AVL b
r) Int#
h = AVL b
-> Int#
-> b
-> AVL b
-> Int#
-> (# AVL b, Int#, Maybe c, AVL b, Int# #)
forkL__ AVL b
l DECINT1(h) e r DECINT2(h)
forkL__ :: AVL b
-> Int#
-> b
-> AVL b
-> Int#
-> (# AVL b, Int#, Maybe c, AVL b, Int# #)
forkL__ AVL b
l Int#
hl b
e AVL b
r Int#
hr = case a -> b -> COrdering c
cmp a
e0 b
e of
COrdering c
Lt -> case AVL b -> Int# -> (# AVL b, Int#, Maybe c, AVL b, Int# #)
forkL_ AVL b
l Int#
hl of
UBT5(l0,hl0,mbc0,l1,hl1) -> case AVL b -> Int# -> b -> AVL b -> Int# -> (# AVL b, Int# #)
forall e. AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
spliceH AVL b
l1 Int#
hl1 b
e AVL b
r Int#
hr of
UBT2(l1_,hl1_) -> UBT5(l0,hl0,mbc0,l1_,hl1_)
Eq c
c0 -> UBT5(l,hl,Just c0,r,hr)
COrdering c
Gt -> case AVL b -> Int# -> (# AVL b, Int#, Maybe c, AVL b, Int# #)
forkL_ AVL b
r Int#
hr of
UBT5(l0,hl0,mbc0,l1,hl1) -> case AVL b -> Int# -> b -> AVL b -> Int# -> (# AVL b, Int# #)
forall e. AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
spliceH AVL b
l Int#
hl b
e AVL b
l0 Int#
hl0 of
UBT2(l0_,hl0_) -> UBT5(l0_,hl0_,mbc0,l1,hl1)
forkR :: AVL a -> b -> (# AVL a, Int#, Maybe c, AVL a, Int# #)
forkR AVL a
t0 b
e1 = AVL a -> Int# -> (# AVL a, Int#, Maybe c, AVL a, Int# #)
forkR_ AVL a
t0 L(0) where
forkR_ :: AVL a -> Int# -> (# AVL a, Int#, Maybe c, AVL a, Int# #)
forkR_ AVL a
E Int#
h = UBT5(Int#
E,h,Nothing,Int#
E,h)
forkR_ (N AVL a
l a
e AVL a
r) Int#
h = AVL a
-> Int#
-> a
-> AVL a
-> Int#
-> (# AVL a, Int#, Maybe c, AVL a, Int# #)
forkR__ AVL a
l DECINT2(h) e r DECINT1(h)
forkR_ (Z AVL a
l a
e AVL a
r) Int#
h = AVL a
-> Int#
-> a
-> AVL a
-> Int#
-> (# AVL a, Int#, Maybe c, AVL a, Int# #)
forkR__ AVL a
l DECINT1(h) e r DECINT1(h)
forkR_ (P AVL a
l a
e AVL a
r) Int#
h = AVL a
-> Int#
-> a
-> AVL a
-> Int#
-> (# AVL a, Int#, Maybe c, AVL a, Int# #)
forkR__ AVL a
l DECINT1(h) e r DECINT2(h)
forkR__ :: AVL a
-> Int#
-> a
-> AVL a
-> Int#
-> (# AVL a, Int#, Maybe c, AVL a, Int# #)
forkR__ AVL a
l Int#
hl a
e AVL a
r Int#
hr = case a -> b -> COrdering c
cmp a
e b
e1 of
COrdering c
Lt -> case AVL a -> Int# -> (# AVL a, Int#, Maybe c, AVL a, Int# #)
forkR_ AVL a
r Int#
hr of
UBT5(l0,hl0,mbc1,l1,hl1) -> case AVL a -> Int# -> a -> AVL a -> Int# -> (# AVL a, Int# #)
forall e. AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
spliceH AVL a
l Int#
hl a
e AVL a
l0 Int#
hl0 of
UBT2(l0_,hl0_) -> UBT5(l0_,hl0_,mbc1,l1,hl1)
Eq c
c1 -> UBT5(l,hl,Just c1,r,hr)
COrdering c
Gt -> case AVL a -> Int# -> (# AVL a, Int#, Maybe c, AVL a, Int# #)
forkR_ AVL a
l Int#
hl of
UBT5(l0,hl0,mbc1,l1,hl1) -> case AVL a -> Int# -> a -> AVL a -> Int# -> (# AVL a, Int# #)
forall e. AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
spliceH AVL a
l1 Int#
hl1 a
e AVL a
r Int#
hr of
UBT2(l1_,hl1_) -> UBT5(l0,hl0,mbc1,l1_,hl1_)
intersectionMaybeH :: (a -> b -> COrdering (Maybe c)) -> AVL a -> AVL b -> UBT2(AVL c,UINT)
intersectionMaybeH :: forall a b c.
(a -> b -> COrdering (Maybe c))
-> AVL a -> AVL b -> (# AVL c, Int# #)
intersectionMaybeH a -> b -> COrdering (Maybe c)
comp = AVL a -> AVL b -> (# AVL c, Int# #)
i where
i :: AVL a -> AVL b -> (# AVL c, Int# #)
i AVL a
E AVL b
_ = UBT2(E,L(0))
i AVL a
_ AVL b
E = UBT2(E,L(0))
i (N AVL a
l0 a
e0 AVL a
r0) (N AVL b
l1 b
e1 AVL b
r1) = AVL a -> a -> AVL a -> AVL b -> b -> AVL b -> (# AVL c, Int# #)
i_ AVL a
l0 a
e0 AVL a
r0 AVL b
l1 b
e1 AVL b
r1
i (N AVL a
l0 a
e0 AVL a
r0) (Z AVL b
l1 b
e1 AVL b
r1) = AVL a -> a -> AVL a -> AVL b -> b -> AVL b -> (# AVL c, Int# #)
i_ AVL a
l0 a
e0 AVL a
r0 AVL b
l1 b
e1 AVL b
r1
i (N AVL a
l0 a
e0 AVL a
r0) (P AVL b
l1 b
e1 AVL b
r1) = AVL a -> a -> AVL a -> AVL b -> b -> AVL b -> (# AVL c, Int# #)
i_ AVL a
l0 a
e0 AVL a
r0 AVL b
l1 b
e1 AVL b
r1
i (Z AVL a
l0 a
e0 AVL a
r0) (N AVL b
l1 b
e1 AVL b
r1) = AVL a -> a -> AVL a -> AVL b -> b -> AVL b -> (# AVL c, Int# #)
i_ AVL a
l0 a
e0 AVL a
r0 AVL b
l1 b
e1 AVL b
r1
i (Z AVL a
l0 a
e0 AVL a
r0) (Z AVL b
l1 b
e1 AVL b
r1) = AVL a -> a -> AVL a -> AVL b -> b -> AVL b -> (# AVL c, Int# #)
i_ AVL a
l0 a
e0 AVL a
r0 AVL b
l1 b
e1 AVL b
r1
i (Z AVL a
l0 a
e0 AVL a
r0) (P AVL b
l1 b
e1 AVL b
r1) = AVL a -> a -> AVL a -> AVL b -> b -> AVL b -> (# AVL c, Int# #)
i_ AVL a
l0 a
e0 AVL a
r0 AVL b
l1 b
e1 AVL b
r1
i (P AVL a
l0 a
e0 AVL a
r0) (N AVL b
l1 b
e1 AVL b
r1) = AVL a -> a -> AVL a -> AVL b -> b -> AVL b -> (# AVL c, Int# #)
i_ AVL a
l0 a
e0 AVL a
r0 AVL b
l1 b
e1 AVL b
r1
i (P AVL a
l0 a
e0 AVL a
r0) (Z AVL b
l1 b
e1 AVL b
r1) = AVL a -> a -> AVL a -> AVL b -> b -> AVL b -> (# AVL c, Int# #)
i_ AVL a
l0 a
e0 AVL a
r0 AVL b
l1 b
e1 AVL b
r1
i (P AVL a
l0 a
e0 AVL a
r0) (P AVL b
l1 b
e1 AVL b
r1) = AVL a -> a -> AVL a -> AVL b -> b -> AVL b -> (# AVL c, Int# #)
i_ AVL a
l0 a
e0 AVL a
r0 AVL b
l1 b
e1 AVL b
r1
i_ :: AVL a -> a -> AVL a -> AVL b -> b -> AVL b -> (# AVL c, Int# #)
i_ AVL a
l0 a
e0 AVL a
r0 AVL b
l1 b
e1 AVL b
r1 =
case a -> b -> COrdering (Maybe c)
comp a
e0 b
e1 of
COrdering (Maybe c)
Lt -> case AVL a -> b -> (# AVL a, Int#, Maybe c, AVL a, Int# #)
forkR AVL a
r0 b
e1 of
UBT5(rl0,_,mbc1,rr0,_) -> case a -> AVL b -> (# AVL b, Int#, Maybe c, AVL b, Int# #)
forkL a
e0 AVL b
l1 of
UBT5(ll1,_,mbc0,lr1,_) ->
case AVL a -> AVL b -> (# AVL c, Int# #)
i AVL a
rr0 AVL b
r1 of
UBT2(r,hr) -> case AVL a -> AVL b -> (# AVL c, Int# #)
i AVL a
rl0 AVL b
lr1 of
UBT2(m,hm) -> case AVL a -> AVL b -> (# AVL c, Int# #)
i AVL a
l0 AVL b
ll1 of
UBT2(l,hl) -> case (case Maybe c
mbc1 of
Just c
c1 -> AVL c -> Int# -> c -> AVL c -> Int# -> (# AVL c, Int# #)
forall e. AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
spliceH AVL c
m Int#
hm c
c1 AVL c
r Int#
hr
Maybe c
Nothing -> AVL c -> Int# -> AVL c -> Int# -> (# AVL c, Int# #)
forall e. AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
joinH AVL c
m Int#
hm AVL c
r Int#
hr
) of
UBT2(t,ht) -> case Maybe c
mbc0 of
Just c
c0 -> AVL c -> Int# -> c -> AVL c -> Int# -> (# AVL c, Int# #)
forall e. AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
spliceH AVL c
l Int#
hl c
c0 AVL c
t Int#
ht
Maybe c
Nothing -> AVL c -> Int# -> AVL c -> Int# -> (# AVL c, Int# #)
forall e. AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
joinH AVL c
l Int#
hl AVL c
t Int#
ht
Eq Maybe c
mbc -> case AVL a -> AVL b -> (# AVL c, Int# #)
i AVL a
l0 AVL b
l1 of
UBT2(l,hl) -> case AVL a -> AVL b -> (# AVL c, Int# #)
i AVL a
r0 AVL b
r1 of
UBT2(r,hr) -> case Maybe c
mbc of
Just c
c -> AVL c -> Int# -> c -> AVL c -> Int# -> (# AVL c, Int# #)
forall e. AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
spliceH AVL c
l Int#
hl c
c AVL c
r Int#
hr
Maybe c
Nothing -> AVL c -> Int# -> AVL c -> Int# -> (# AVL c, Int# #)
forall e. AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
joinH AVL c
l Int#
hl AVL c
r Int#
hr
COrdering (Maybe c)
Gt -> case a -> AVL b -> (# AVL b, Int#, Maybe c, AVL b, Int# #)
forkL a
e0 AVL b
r1 of
UBT5(rl1,_,mbc0,rr1,_) -> case AVL a -> b -> (# AVL a, Int#, Maybe c, AVL a, Int# #)
forkR AVL a
l0 b
e1 of
UBT5(ll0,_,mbc1,lr0,_) ->
case AVL a -> AVL b -> (# AVL c, Int# #)
i AVL a
r0 AVL b
rr1 of
UBT2(r,hr) -> case AVL a -> AVL b -> (# AVL c, Int# #)
i AVL a
lr0 AVL b
rl1 of
UBT2(m,hm) -> case AVL a -> AVL b -> (# AVL c, Int# #)
i AVL a
ll0 AVL b
l1 of
UBT2(l,hl) -> case (case Maybe c
mbc0 of
Just c
c0 -> AVL c -> Int# -> c -> AVL c -> Int# -> (# AVL c, Int# #)
forall e. AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
spliceH AVL c
m Int#
hm c
c0 AVL c
r Int#
hr
Maybe c
Nothing -> AVL c -> Int# -> AVL c -> Int# -> (# AVL c, Int# #)
forall e. AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
joinH AVL c
m Int#
hm AVL c
r Int#
hr
) of
UBT2(t,ht) -> case Maybe c
mbc1 of
Just c
c1 -> AVL c -> Int# -> c -> AVL c -> Int# -> (# AVL c, Int# #)
forall e. AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
spliceH AVL c
l Int#
hl c
c1 AVL c
t Int#
ht
Maybe c
Nothing -> AVL c -> Int# -> AVL c -> Int# -> (# AVL c, Int# #)
forall e. AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
joinH AVL c
l Int#
hl AVL c
t Int#
ht
forkL :: a -> AVL b -> (# AVL b, Int#, Maybe c, AVL b, Int# #)
forkL a
e0 AVL b
t1 = AVL b -> Int# -> (# AVL b, Int#, Maybe c, AVL b, Int# #)
forkL_ AVL b
t1 L(0) where
forkL_ :: AVL b -> Int# -> (# AVL b, Int#, Maybe c, AVL b, Int# #)
forkL_ AVL b
E Int#
h = UBT5(Int#
E,h,Nothing,Int#
E,h)
forkL_ (N AVL b
l b
e AVL b
r) Int#
h = AVL b
-> Int#
-> b
-> AVL b
-> Int#
-> (# AVL b, Int#, Maybe c, AVL b, Int# #)
forkL__ AVL b
l DECINT2(h) e r DECINT1(h)
forkL_ (Z AVL b
l b
e AVL b
r) Int#
h = AVL b
-> Int#
-> b
-> AVL b
-> Int#
-> (# AVL b, Int#, Maybe c, AVL b, Int# #)
forkL__ AVL b
l DECINT1(h) e r DECINT1(h)
forkL_ (P AVL b
l b
e AVL b
r) Int#
h = AVL b
-> Int#
-> b
-> AVL b
-> Int#
-> (# AVL b, Int#, Maybe c, AVL b, Int# #)
forkL__ AVL b
l DECINT1(h) e r DECINT2(h)
forkL__ :: AVL b
-> Int#
-> b
-> AVL b
-> Int#
-> (# AVL b, Int#, Maybe c, AVL b, Int# #)
forkL__ AVL b
l Int#
hl b
e AVL b
r Int#
hr = case a -> b -> COrdering (Maybe c)
comp a
e0 b
e of
COrdering (Maybe c)
Lt -> case AVL b -> Int# -> (# AVL b, Int#, Maybe c, AVL b, Int# #)
forkL_ AVL b
l Int#
hl of
UBT5(l0,hl0,mbc0,l1,hl1) -> case AVL b -> Int# -> b -> AVL b -> Int# -> (# AVL b, Int# #)
forall e. AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
spliceH AVL b
l1 Int#
hl1 b
e AVL b
r Int#
hr of
UBT2(l1_,hl1_) -> UBT5(l0,hl0,mbc0,l1_,hl1_)
Eq Maybe c
mbc0_ -> UBT5(l,hl,mbc0_,r,hr)
COrdering (Maybe c)
Gt -> case AVL b -> Int# -> (# AVL b, Int#, Maybe c, AVL b, Int# #)
forkL_ AVL b
r Int#
hr of
UBT5(l0,hl0,mbc0,l1,hl1) -> case AVL b -> Int# -> b -> AVL b -> Int# -> (# AVL b, Int# #)
forall e. AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
spliceH AVL b
l Int#
hl b
e AVL b
l0 Int#
hl0 of
UBT2(l0_,hl0_) -> UBT5(l0_,hl0_,mbc0,l1,hl1)
forkR :: AVL a -> b -> (# AVL a, Int#, Maybe c, AVL a, Int# #)
forkR AVL a
t0 b
e1 = AVL a -> Int# -> (# AVL a, Int#, Maybe c, AVL a, Int# #)
forkR_ AVL a
t0 L(0) where
forkR_ :: AVL a -> Int# -> (# AVL a, Int#, Maybe c, AVL a, Int# #)
forkR_ AVL a
E Int#
h = UBT5(Int#
E,h,Nothing,Int#
E,h)
forkR_ (N AVL a
l a
e AVL a
r) Int#
h = AVL a
-> Int#
-> a
-> AVL a
-> Int#
-> (# AVL a, Int#, Maybe c, AVL a, Int# #)
forkR__ AVL a
l DECINT2(h) e r DECINT1(h)
forkR_ (Z AVL a
l a
e AVL a
r) Int#
h = AVL a
-> Int#
-> a
-> AVL a
-> Int#
-> (# AVL a, Int#, Maybe c, AVL a, Int# #)
forkR__ AVL a
l DECINT1(h) e r DECINT1(h)
forkR_ (P AVL a
l a
e AVL a
r) Int#
h = AVL a
-> Int#
-> a
-> AVL a
-> Int#
-> (# AVL a, Int#, Maybe c, AVL a, Int# #)
forkR__ AVL a
l DECINT1(h) e r DECINT2(h)
forkR__ :: AVL a
-> Int#
-> a
-> AVL a
-> Int#
-> (# AVL a, Int#, Maybe c, AVL a, Int# #)
forkR__ AVL a
l Int#
hl a
e AVL a
r Int#
hr = case a -> b -> COrdering (Maybe c)
comp a
e b
e1 of
COrdering (Maybe c)
Lt -> case AVL a -> Int# -> (# AVL a, Int#, Maybe c, AVL a, Int# #)
forkR_ AVL a
r Int#
hr of
UBT5(l0,hl0,mbc1,l1,hl1) -> case AVL a -> Int# -> a -> AVL a -> Int# -> (# AVL a, Int# #)
forall e. AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
spliceH AVL a
l Int#
hl a
e AVL a
l0 Int#
hl0 of
UBT2(l0_,hl0_) -> UBT5(l0_,hl0_,mbc1,l1,hl1)
Eq Maybe c
mbc1_ -> UBT5(l,hl,mbc1_,r,hr)
COrdering (Maybe c)
Gt -> case AVL a -> Int# -> (# AVL a, Int#, Maybe c, AVL a, Int# #)
forkR_ AVL a
l Int#
hl of
UBT5(l0,hl0,mbc1,l1,hl1) -> case AVL a -> Int# -> a -> AVL a -> Int# -> (# AVL a, Int# #)
forall e. AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
spliceH AVL a
l1 Int#
hl1 a
e AVL a
r Int#
hr of
UBT2(l1_,hl1_) -> UBT5(l0,hl0,mbc1,l1_,hl1_)
differenceH :: (a -> b -> Ordering) -> AVL a -> UINT -> AVL b -> UBT2(AVL a,UINT)
differenceH :: forall a b.
(a -> b -> Ordering) -> AVL a -> Int# -> AVL b -> (# AVL a, Int# #)
differenceH a -> b -> Ordering
comp = AVL a -> Int# -> AVL b -> (# AVL a, Int# #)
d where
d :: AVL a -> Int# -> AVL b -> (# AVL a, Int# #)
d AVL a
E Int#
h0 AVL b
_ = UBT2(E ,h0)
d AVL a
t0 Int#
h0 AVL b
E = UBT2(t0,h0)
d (N AVL a
l0 a
e0 AVL a
r0) Int#
h0 (N AVL b
l1 b
e1 AVL b
r1) = AVL a
-> Int#
-> a
-> AVL a
-> Int#
-> AVL b
-> b
-> AVL b
-> (# AVL a, Int# #)
d_ AVL a
l0 DECINT2(h0) e0 r0 DECINT1(h0) l1 e1 r1
d (N AVL a
l0 a
e0 AVL a
r0) Int#
h0 (Z AVL b
l1 b
e1 AVL b
r1) = AVL a
-> Int#
-> a
-> AVL a
-> Int#
-> AVL b
-> b
-> AVL b
-> (# AVL a, Int# #)
d_ AVL a
l0 DECINT2(h0) e0 r0 DECINT1(h0) l1 e1 r1
d (N AVL a
l0 a
e0 AVL a
r0) Int#
h0 (P AVL b
l1 b
e1 AVL b
r1) = AVL a
-> Int#
-> a
-> AVL a
-> Int#
-> AVL b
-> b
-> AVL b
-> (# AVL a, Int# #)
d_ AVL a
l0 DECINT2(h0) e0 r0 DECINT1(h0) l1 e1 r1
d (Z AVL a
l0 a
e0 AVL a
r0) Int#
h0 (N AVL b
l1 b
e1 AVL b
r1) = AVL a
-> Int#
-> a
-> AVL a
-> Int#
-> AVL b
-> b
-> AVL b
-> (# AVL a, Int# #)
d_ AVL a
l0 DECINT1(h0) e0 r0 DECINT1(h0) l1 e1 r1
d (Z AVL a
l0 a
e0 AVL a
r0) Int#
h0 (Z AVL b
l1 b
e1 AVL b
r1) = AVL a
-> Int#
-> a
-> AVL a
-> Int#
-> AVL b
-> b
-> AVL b
-> (# AVL a, Int# #)
d_ AVL a
l0 DECINT1(h0) e0 r0 DECINT1(h0) l1 e1 r1
d (Z AVL a
l0 a
e0 AVL a
r0) Int#
h0 (P AVL b
l1 b
e1 AVL b
r1) = AVL a
-> Int#
-> a
-> AVL a
-> Int#
-> AVL b
-> b
-> AVL b
-> (# AVL a, Int# #)
d_ AVL a
l0 DECINT1(h0) e0 r0 DECINT1(h0) l1 e1 r1
d (P AVL a
l0 a
e0 AVL a
r0) Int#
h0 (N AVL b
l1 b
e1 AVL b
r1) = AVL a
-> Int#
-> a
-> AVL a
-> Int#
-> AVL b
-> b
-> AVL b
-> (# AVL a, Int# #)
d_ AVL a
l0 DECINT1(h0) e0 r0 DECINT2(h0) l1 e1 r1
d (P AVL a
l0 a
e0 AVL a
r0) Int#
h0 (Z AVL b
l1 b
e1 AVL b
r1) = AVL a
-> Int#
-> a
-> AVL a
-> Int#
-> AVL b
-> b
-> AVL b
-> (# AVL a, Int# #)
d_ AVL a
l0 DECINT1(h0) e0 r0 DECINT2(h0) l1 e1 r1
d (P AVL a
l0 a
e0 AVL a
r0) Int#
h0 (P AVL b
l1 b
e1 AVL b
r1) = AVL a
-> Int#
-> a
-> AVL a
-> Int#
-> AVL b
-> b
-> AVL b
-> (# AVL a, Int# #)
d_ AVL a
l0 DECINT1(h0) e0 r0 DECINT2(h0) l1 e1 r1
d_ :: AVL a
-> Int#
-> a
-> AVL a
-> Int#
-> AVL b
-> b
-> AVL b
-> (# AVL a, Int# #)
d_ AVL a
l0 Int#
hl0 a
e0 AVL a
r0 Int#
hr0 AVL b
l1 b
e1 AVL b
r1 =
case a -> b -> Ordering
comp a
e0 b
e1 of
Ordering
LT -> case AVL a -> Int# -> b -> (# AVL a, Int#, AVL a, Int# #)
forkR AVL a
r0 Int#
hr0 b
e1 of
UBT4(rl0,hrl0, rr0,hrr0) -> case a -> AVL b -> (# AVL b, Int#, Bool, AVL b, Int# #)
forkL a
e0 AVL b
l1 of
UBT5(ll1,_ ,be0,lr1,_ ) ->
case AVL a -> Int# -> AVL b -> (# AVL a, Int# #)
d AVL a
rr0 Int#
hrr0 AVL b
r1 of
UBT2(r,hr) -> case AVL a -> Int# -> AVL b -> (# AVL a, Int# #)
d AVL a
rl0 Int#
hrl0 AVL b
lr1 of
UBT2(m,hm) -> case AVL a -> Int# -> AVL b -> (# AVL a, Int# #)
d AVL a
l0 Int#
hl0 AVL b
ll1 of
UBT2(l,hl) -> case AVL a -> Int# -> AVL a -> Int# -> (# AVL a, Int# #)
forall e. AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
joinH AVL a
m Int#
hm AVL a
r Int#
hr of
UBT2(y,hy) -> if Bool
be0
then AVL a -> Int# -> a -> AVL a -> Int# -> (# AVL a, Int# #)
forall e. AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
spliceH AVL a
l Int#
hl a
e0 AVL a
y Int#
hy
else AVL a -> Int# -> AVL a -> Int# -> (# AVL a, Int# #)
forall e. AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
joinH AVL a
l Int#
hl AVL a
y Int#
hy
Ordering
EQ -> case AVL a -> Int# -> AVL b -> (# AVL a, Int# #)
d AVL a
r0 Int#
hr0 AVL b
r1 of
UBT2(r,hr) -> case AVL a -> Int# -> AVL b -> (# AVL a, Int# #)
d AVL a
l0 Int#
hl0 AVL b
l1 of
UBT2(l,hl) -> AVL a -> Int# -> AVL a -> Int# -> (# AVL a, Int# #)
forall e. AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
joinH AVL a
l Int#
hl AVL a
r Int#
hr
Ordering
GT -> case a -> AVL b -> (# AVL b, Int#, Bool, AVL b, Int# #)
forkL a
e0 AVL b
r1 of
UBT5(rl1,_ ,be0,rr1,_ ) -> case AVL a -> Int# -> b -> (# AVL a, Int#, AVL a, Int# #)
forkR AVL a
l0 Int#
hl0 b
e1 of
UBT4(ll0,hll0, lr0,hlr0) ->
case AVL a -> Int# -> AVL b -> (# AVL a, Int# #)
d AVL a
r0 Int#
hr0 AVL b
rr1 of
UBT2(r,hr) -> case AVL a -> Int# -> AVL b -> (# AVL a, Int# #)
d AVL a
lr0 Int#
hlr0 AVL b
rl1 of
UBT2(m,hm) -> case AVL a -> Int# -> AVL b -> (# AVL a, Int# #)
d AVL a
ll0 Int#
hll0 AVL b
l1 of
UBT2(l,hl) -> case AVL a -> Int# -> AVL a -> Int# -> (# AVL a, Int# #)
forall e. AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
joinH AVL a
l Int#
hl AVL a
m Int#
hm of
UBT2(x,hx) -> if Bool
be0
then AVL a -> Int# -> a -> AVL a -> Int# -> (# AVL a, Int# #)
forall e. AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
spliceH AVL a
x Int#
hx a
e0 AVL a
r Int#
hr
else AVL a -> Int# -> AVL a -> Int# -> (# AVL a, Int# #)
forall e. AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
joinH AVL a
x Int#
hx AVL a
r Int#
hr
forkL :: a -> AVL b -> (# AVL b, Int#, Bool, AVL b, Int# #)
forkL a
e0 AVL b
t1 = AVL b -> Int# -> (# AVL b, Int#, Bool, AVL b, Int# #)
forkL_ AVL b
t1 L(0) where
forkL_ :: AVL b -> Int# -> (# AVL b, Int#, Bool, AVL b, Int# #)
forkL_ AVL b
E Int#
h = UBT5(Int#
E,h,True,Int#
E,h)
forkL_ (N AVL b
l b
e AVL b
r) Int#
h = AVL b
-> Int#
-> b
-> AVL b
-> Int#
-> (# AVL b, Int#, Bool, AVL b, Int# #)
forkL__ AVL b
l DECINT2(h) e r DECINT1(h)
forkL_ (Z AVL b
l b
e AVL b
r) Int#
h = AVL b
-> Int#
-> b
-> AVL b
-> Int#
-> (# AVL b, Int#, Bool, AVL b, Int# #)
forkL__ AVL b
l DECINT1(h) e r DECINT1(h)
forkL_ (P AVL b
l b
e AVL b
r) Int#
h = AVL b
-> Int#
-> b
-> AVL b
-> Int#
-> (# AVL b, Int#, Bool, AVL b, Int# #)
forkL__ AVL b
l DECINT1(h) e r DECINT2(h)
forkL__ :: AVL b
-> Int#
-> b
-> AVL b
-> Int#
-> (# AVL b, Int#, Bool, AVL b, Int# #)
forkL__ AVL b
l Int#
hl b
e AVL b
r Int#
hr = case a -> b -> Ordering
comp a
e0 b
e of
Ordering
LT -> case AVL b -> Int# -> (# AVL b, Int#, Bool, AVL b, Int# #)
forkL_ AVL b
l Int#
hl of
UBT5(x0,hx0,be0,x1,hx1) -> case AVL b -> Int# -> b -> AVL b -> Int# -> (# AVL b, Int# #)
forall e. AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
spliceH AVL b
x1 Int#
hx1 b
e AVL b
r Int#
hr of
UBT2(x1_,hx1_) -> UBT5(x0,hx0,be0,x1_,hx1_)
Ordering
EQ -> UBT5(l,hl,False,r,hr)
Ordering
GT -> case AVL b -> Int# -> (# AVL b, Int#, Bool, AVL b, Int# #)
forkL_ AVL b
r Int#
hr of
UBT5(x0,hx0,be0,x1,hx1) -> case AVL b -> Int# -> b -> AVL b -> Int# -> (# AVL b, Int# #)
forall e. AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
spliceH AVL b
l Int#
hl b
e AVL b
x0 Int#
hx0 of
UBT2(x0_,hx0_) -> UBT5(x0_,hx0_,be0,x1,hx1)
forkR :: AVL a -> Int# -> b -> (# AVL a, Int#, AVL a, Int# #)
forkR AVL a
t0 Int#
ht0 b
e1 = AVL a -> Int# -> (# AVL a, Int#, AVL a, Int# #)
forkR_ AVL a
t0 Int#
ht0 where
forkR_ :: AVL a -> Int# -> (# AVL a, Int#, AVL a, Int# #)
forkR_ AVL a
E Int#
h = UBT4(Int#
E,AVL a
forall e. AVL e
h,Int#
E,h)
forkR_ (N AVL a
l a
e AVL a
r) Int#
h = AVL a
-> Int# -> a -> AVL a -> Int# -> (# AVL a, Int#, AVL a, Int# #)
forkR__ AVL a
l DECINT2(h) e r DECINT1(h)
forkR_ (Z AVL a
l a
e AVL a
r) Int#
h = AVL a
-> Int# -> a -> AVL a -> Int# -> (# AVL a, Int#, AVL a, Int# #)
forkR__ AVL a
l DECINT1(h) e r DECINT1(h)
forkR_ (P AVL a
l a
e AVL a
r) Int#
h = AVL a
-> Int# -> a -> AVL a -> Int# -> (# AVL a, Int#, AVL a, Int# #)
forkR__ AVL a
l DECINT1(h) e r DECINT2(h)
forkR__ :: AVL a
-> Int# -> a -> AVL a -> Int# -> (# AVL a, Int#, AVL a, Int# #)
forkR__ AVL a
l Int#
hl a
e AVL a
r Int#
hr = case a -> b -> Ordering
comp a
e b
e1 of
Ordering
LT -> case AVL a -> Int# -> (# AVL a, Int#, AVL a, Int# #)
forkR_ AVL a
r Int#
hr of
UBT4(x0,hx0,x1,hx1) -> case AVL a -> Int# -> a -> AVL a -> Int# -> (# AVL a, Int# #)
forall e. AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
spliceH AVL a
l Int#
hl a
e AVL a
x0 Int#
hx0 of
UBT2(x0_,hx0_) -> UBT4(x0_,hx0_,x1,hx1)
Ordering
EQ -> UBT4(l,hl,r,hr)
Ordering
GT -> case AVL a -> Int# -> (# AVL a, Int#, AVL a, Int# #)
forkR_ AVL a
l Int#
hl of
UBT4(x0,hx0,x1,hx1) -> case AVL a -> Int# -> a -> AVL a -> Int# -> (# AVL a, Int# #)
forall e. AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
spliceH AVL a
x1 Int#
hx1 a
e AVL a
r Int#
hr of
UBT2(x1_,hx1_) -> UBT4(x0,hx0,x1_,hx1_)
differenceMaybeH :: (a -> b -> COrdering (Maybe a)) -> AVL a -> UINT -> AVL b -> UBT2(AVL a,UINT)
differenceMaybeH :: forall a b.
(a -> b -> COrdering (Maybe a))
-> AVL a -> Int# -> AVL b -> (# AVL a, Int# #)
differenceMaybeH a -> b -> COrdering (Maybe a)
comp = AVL a -> Int# -> AVL b -> (# AVL a, Int# #)
d where
d :: AVL a -> Int# -> AVL b -> (# AVL a, Int# #)
d AVL a
E Int#
h0 AVL b
_ = UBT2(E ,h0)
d AVL a
t0 Int#
h0 AVL b
E = UBT2(t0,h0)
d (N AVL a
l0 a
e0 AVL a
r0) Int#
h0 (N AVL b
l1 b
e1 AVL b
r1) = AVL a
-> Int#
-> a
-> AVL a
-> Int#
-> AVL b
-> b
-> AVL b
-> (# AVL a, Int# #)
d_ AVL a
l0 DECINT2(h0) e0 r0 DECINT1(h0) l1 e1 r1
d (N AVL a
l0 a
e0 AVL a
r0) Int#
h0 (Z AVL b
l1 b
e1 AVL b
r1) = AVL a
-> Int#
-> a
-> AVL a
-> Int#
-> AVL b
-> b
-> AVL b
-> (# AVL a, Int# #)
d_ AVL a
l0 DECINT2(h0) e0 r0 DECINT1(h0) l1 e1 r1
d (N AVL a
l0 a
e0 AVL a
r0) Int#
h0 (P AVL b
l1 b
e1 AVL b
r1) = AVL a
-> Int#
-> a
-> AVL a
-> Int#
-> AVL b
-> b
-> AVL b
-> (# AVL a, Int# #)
d_ AVL a
l0 DECINT2(h0) e0 r0 DECINT1(h0) l1 e1 r1
d (Z AVL a
l0 a
e0 AVL a
r0) Int#
h0 (N AVL b
l1 b
e1 AVL b
r1) = AVL a
-> Int#
-> a
-> AVL a
-> Int#
-> AVL b
-> b
-> AVL b
-> (# AVL a, Int# #)
d_ AVL a
l0 DECINT1(h0) e0 r0 DECINT1(h0) l1 e1 r1
d (Z AVL a
l0 a
e0 AVL a
r0) Int#
h0 (Z AVL b
l1 b
e1 AVL b
r1) = AVL a
-> Int#
-> a
-> AVL a
-> Int#
-> AVL b
-> b
-> AVL b
-> (# AVL a, Int# #)
d_ AVL a
l0 DECINT1(h0) e0 r0 DECINT1(h0) l1 e1 r1
d (Z AVL a
l0 a
e0 AVL a
r0) Int#
h0 (P AVL b
l1 b
e1 AVL b
r1) = AVL a
-> Int#
-> a
-> AVL a
-> Int#
-> AVL b
-> b
-> AVL b
-> (# AVL a, Int# #)
d_ AVL a
l0 DECINT1(h0) e0 r0 DECINT1(h0) l1 e1 r1
d (P AVL a
l0 a
e0 AVL a
r0) Int#
h0 (N AVL b
l1 b
e1 AVL b
r1) = AVL a
-> Int#
-> a
-> AVL a
-> Int#
-> AVL b
-> b
-> AVL b
-> (# AVL a, Int# #)
d_ AVL a
l0 DECINT1(h0) e0 r0 DECINT2(h0) l1 e1 r1
d (P AVL a
l0 a
e0 AVL a
r0) Int#
h0 (Z AVL b
l1 b
e1 AVL b
r1) = AVL a
-> Int#
-> a
-> AVL a
-> Int#
-> AVL b
-> b
-> AVL b
-> (# AVL a, Int# #)
d_ AVL a
l0 DECINT1(h0) e0 r0 DECINT2(h0) l1 e1 r1
d (P AVL a
l0 a
e0 AVL a
r0) Int#
h0 (P AVL b
l1 b
e1 AVL b
r1) = AVL a
-> Int#
-> a
-> AVL a
-> Int#
-> AVL b
-> b
-> AVL b
-> (# AVL a, Int# #)
d_ AVL a
l0 DECINT1(h0) e0 r0 DECINT2(h0) l1 e1 r1
d_ :: AVL a
-> Int#
-> a
-> AVL a
-> Int#
-> AVL b
-> b
-> AVL b
-> (# AVL a, Int# #)
d_ AVL a
l0 Int#
hl0 a
e0 AVL a
r0 Int#
hr0 AVL b
l1 b
e1 AVL b
r1 =
case a -> b -> COrdering (Maybe a)
comp a
e0 b
e1 of
COrdering (Maybe a)
Lt -> case AVL a -> Int# -> b -> (# AVL a, Int#, Maybe a, AVL a, Int# #)
forkR AVL a
r0 Int#
hr0 b
e1 of
UBT5( rl0,hrl0,mbe1,rr0,hrr0) -> case a -> AVL b -> (# AVL b, Int#, Maybe a, AVL b, Int# #)
forkL a
e0 AVL b
l1 of
UBT5(ll1,_ ,mbe0,lr1,_ ) ->
case AVL a -> Int# -> AVL b -> (# AVL a, Int# #)
d AVL a
rr0 Int#
hrr0 AVL b
r1 of
UBT2(r,hr) -> case AVL a -> Int# -> AVL b -> (# AVL a, Int# #)
d AVL a
rl0 Int#
hrl0 AVL b
lr1 of
UBT2(m,hm) -> case AVL a -> Int# -> AVL b -> (# AVL a, Int# #)
d AVL a
l0 Int#
hl0 AVL b
ll1 of
UBT2(l,hl) -> case (case Maybe a
mbe1 of
Just a
e1_ -> AVL a -> Int# -> a -> AVL a -> Int# -> (# AVL a, Int# #)
forall e. AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
spliceH AVL a
m Int#
hm a
e1_ AVL a
r Int#
hr
Maybe a
Nothing -> AVL a -> Int# -> AVL a -> Int# -> (# AVL a, Int# #)
forall e. AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
joinH AVL a
m Int#
hm AVL a
r Int#
hr) of
UBT2(y,hy) -> case Maybe a
mbe0 of
Just a
e0_ -> AVL a -> Int# -> a -> AVL a -> Int# -> (# AVL a, Int# #)
forall e. AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
spliceH AVL a
l Int#
hl a
e0_ AVL a
y Int#
hy
Maybe a
Nothing -> AVL a -> Int# -> AVL a -> Int# -> (# AVL a, Int# #)
forall e. AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
joinH AVL a
l Int#
hl AVL a
y Int#
hy
Eq Maybe a
mbe0 -> case AVL a -> Int# -> AVL b -> (# AVL a, Int# #)
d AVL a
r0 Int#
hr0 AVL b
r1 of
UBT2(r,hr) -> case AVL a -> Int# -> AVL b -> (# AVL a, Int# #)
d AVL a
l0 Int#
hl0 AVL b
l1 of
UBT2(l,hl) -> case Maybe a
mbe0 of
Just a
e0_ -> AVL a -> Int# -> a -> AVL a -> Int# -> (# AVL a, Int# #)
forall e. AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
spliceH AVL a
l Int#
hl a
e0_ AVL a
r Int#
hr
Maybe a
Nothing -> AVL a -> Int# -> AVL a -> Int# -> (# AVL a, Int# #)
forall e. AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
joinH AVL a
l Int#
hl AVL a
r Int#
hr
COrdering (Maybe a)
Gt -> case a -> AVL b -> (# AVL b, Int#, Maybe a, AVL b, Int# #)
forkL a
e0 AVL b
r1 of
UBT5( rl1,_ ,mbe0,rr1,_ ) -> case AVL a -> Int# -> b -> (# AVL a, Int#, Maybe a, AVL a, Int# #)
forkR AVL a
l0 Int#
hl0 b
e1 of
UBT5(ll0,hll0,mbe1,lr0,hlr0) ->
case AVL a -> Int# -> AVL b -> (# AVL a, Int# #)
d AVL a
r0 Int#
hr0 AVL b
rr1 of
UBT2(r,hr) -> case AVL a -> Int# -> AVL b -> (# AVL a, Int# #)
d AVL a
lr0 Int#
hlr0 AVL b
rl1 of
UBT2(m,hm) -> case AVL a -> Int# -> AVL b -> (# AVL a, Int# #)
d AVL a
ll0 Int#
hll0 AVL b
l1 of
UBT2(l,hl) -> case (case Maybe a
mbe1 of
Just a
e1_ -> AVL a -> Int# -> a -> AVL a -> Int# -> (# AVL a, Int# #)
forall e. AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
spliceH AVL a
l Int#
hl a
e1_ AVL a
m Int#
hm
Maybe a
Nothing -> AVL a -> Int# -> AVL a -> Int# -> (# AVL a, Int# #)
forall e. AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
joinH AVL a
l Int#
hl AVL a
m Int#
hm) of
UBT2(x,hx) -> case Maybe a
mbe0 of
Just a
e0_ -> AVL a -> Int# -> a -> AVL a -> Int# -> (# AVL a, Int# #)
forall e. AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
spliceH AVL a
x Int#
hx a
e0_ AVL a
r Int#
hr
Maybe a
Nothing -> AVL a -> Int# -> AVL a -> Int# -> (# AVL a, Int# #)
forall e. AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
joinH AVL a
x Int#
hx AVL a
r Int#
hr
forkL :: a -> AVL b -> (# AVL b, Int#, Maybe a, AVL b, Int# #)
forkL a
e0 AVL b
t1 = AVL b -> Int# -> (# AVL b, Int#, Maybe a, AVL b, Int# #)
forkL_ AVL b
t1 L(0) where
forkL_ :: AVL b -> Int# -> (# AVL b, Int#, Maybe a, AVL b, Int# #)
forkL_ AVL b
E Int#
h = UBT5(Int#
E,h,Just e0,Int#
E,h)
forkL_ (N AVL b
l b
e AVL b
r) Int#
h = AVL b
-> Int#
-> b
-> AVL b
-> Int#
-> (# AVL b, Int#, Maybe a, AVL b, Int# #)
forkL__ AVL b
l DECINT2(h) e r DECINT1(h)
forkL_ (Z AVL b
l b
e AVL b
r) Int#
h = AVL b
-> Int#
-> b
-> AVL b
-> Int#
-> (# AVL b, Int#, Maybe a, AVL b, Int# #)
forkL__ AVL b
l DECINT1(h) e r DECINT1(h)
forkL_ (P AVL b
l b
e AVL b
r) Int#
h = AVL b
-> Int#
-> b
-> AVL b
-> Int#
-> (# AVL b, Int#, Maybe a, AVL b, Int# #)
forkL__ AVL b
l DECINT1(h) e r DECINT2(h)
forkL__ :: AVL b
-> Int#
-> b
-> AVL b
-> Int#
-> (# AVL b, Int#, Maybe a, AVL b, Int# #)
forkL__ AVL b
l Int#
hl b
e AVL b
r Int#
hr = case a -> b -> COrdering (Maybe a)
comp a
e0 b
e of
COrdering (Maybe a)
Lt -> case AVL b -> Int# -> (# AVL b, Int#, Maybe a, AVL b, Int# #)
forkL_ AVL b
l Int#
hl of
UBT5(x0,hx0,mbe0,x1,hx1) -> case AVL b -> Int# -> b -> AVL b -> Int# -> (# AVL b, Int# #)
forall e. AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
spliceH AVL b
x1 Int#
hx1 b
e AVL b
r Int#
hr of
UBT2(x1_,hx1_) -> UBT5(x0,hx0,mbe0,x1_,hx1_)
Eq Maybe a
mbe0 -> UBT5(l,hl,mbe0,r,hr)
COrdering (Maybe a)
Gt -> case AVL b -> Int# -> (# AVL b, Int#, Maybe a, AVL b, Int# #)
forkL_ AVL b
r Int#
hr of
UBT5(x0,hx0,mbe0,x1,hx1) -> case AVL b -> Int# -> b -> AVL b -> Int# -> (# AVL b, Int# #)
forall e. AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
spliceH AVL b
l Int#
hl b
e AVL b
x0 Int#
hx0 of
UBT2(x0_,hx0_) -> UBT5(x0_,hx0_,mbe0,x1,hx1)
forkR :: AVL a -> Int# -> b -> (# AVL a, Int#, Maybe a, AVL a, Int# #)
forkR AVL a
t0 Int#
ht0 b
e1 = AVL a -> Int# -> (# AVL a, Int#, Maybe a, AVL a, Int# #)
forkR_ AVL a
t0 Int#
ht0 where
forkR_ :: AVL a -> Int# -> (# AVL a, Int#, Maybe a, AVL a, Int# #)
forkR_ AVL a
E Int#
h = UBT5(Int#
E,h,Nothing,Int#
E,h)
forkR_ (N AVL a
l a
e AVL a
r) Int#
h = AVL a
-> Int#
-> a
-> AVL a
-> Int#
-> (# AVL a, Int#, Maybe a, AVL a, Int# #)
forkR__ AVL a
l DECINT2(h) e r DECINT1(h)
forkR_ (Z AVL a
l a
e AVL a
r) Int#
h = AVL a
-> Int#
-> a
-> AVL a
-> Int#
-> (# AVL a, Int#, Maybe a, AVL a, Int# #)
forkR__ AVL a
l DECINT1(h) e r DECINT1(h)
forkR_ (P AVL a
l a
e AVL a
r) Int#
h = AVL a
-> Int#
-> a
-> AVL a
-> Int#
-> (# AVL a, Int#, Maybe a, AVL a, Int# #)
forkR__ AVL a
l DECINT1(h) e r DECINT2(h)
forkR__ :: AVL a
-> Int#
-> a
-> AVL a
-> Int#
-> (# AVL a, Int#, Maybe a, AVL a, Int# #)
forkR__ AVL a
l Int#
hl a
e AVL a
r Int#
hr = case a -> b -> COrdering (Maybe a)
comp a
e b
e1 of
COrdering (Maybe a)
Lt -> case AVL a -> Int# -> (# AVL a, Int#, Maybe a, AVL a, Int# #)
forkR_ AVL a
r Int#
hr of
UBT5(x0,hx0,mbe1,x1,hx1) -> case AVL a -> Int# -> a -> AVL a -> Int# -> (# AVL a, Int# #)
forall e. AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
spliceH AVL a
l Int#
hl a
e AVL a
x0 Int#
hx0 of
UBT2(x0_,hx0_) -> UBT5(x0_,hx0_,mbe1,x1,hx1)
Eq Maybe a
mbe1 -> UBT5(l,hl,mbe1,r,hr)
COrdering (Maybe a)
Gt -> case AVL a -> Int# -> (# AVL a, Int#, Maybe a, AVL a, Int# #)
forkR_ AVL a
l Int#
hl of
UBT5(x0,hx0,mbe1,x1,hx1) -> case AVL a -> Int# -> a -> AVL a -> Int# -> (# AVL a, Int# #)
forall e. AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
spliceH AVL a
x1 Int#
hx1 a
e AVL a
r Int#
hr of
UBT2(x1_,hx1_) -> UBT5(x0,hx0,mbe1,x1_,hx1_)
symDifferenceH :: (e -> e -> Ordering) -> AVL e -> UINT -> AVL e -> UINT -> UBT2(AVL e,UINT)
symDifferenceH :: forall e.
(e -> e -> Ordering)
-> AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
symDifferenceH e -> e -> Ordering
c = AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
u where
u :: AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
u AVL e
E Int#
_ AVL e
t1 Int#
h1 = UBT2(t1,h1)
u AVL e
t0 Int#
h0 AVL e
E Int#
_ = UBT2(t0,h0)
u (N AVL e
l0 e
e0 AVL e
r0) Int#
h0 (N AVL e
l1 e
e1 AVL e
r1) Int#
h1 = AVL e
-> Int#
-> e
-> AVL e
-> Int#
-> AVL e
-> Int#
-> e
-> AVL e
-> Int#
-> (# AVL e, Int# #)
u_ AVL e
l0 DECINT2(h0) e0 r0 DECINT1(h0) l1 DECINT2(h1) AVL e
e1 r1 DECINT1(h1)
u (N AVL e
l0 e
e0 AVL e
r0) Int#
h0 (Z AVL e
l1 e
e1 AVL e
r1) Int#
h1 = AVL e
-> Int#
-> e
-> AVL e
-> Int#
-> AVL e
-> Int#
-> e
-> AVL e
-> Int#
-> (# AVL e, Int# #)
u_ AVL e
l0 DECINT2(h0) e0 r0 DECINT1(h0) l1 DECINT1(h1) AVL e
e1 r1 DECINT1(h1)
u (N AVL e
l0 e
e0 AVL e
r0) Int#
h0 (P AVL e
l1 e
e1 AVL e
r1) Int#
h1 = AVL e
-> Int#
-> e
-> AVL e
-> Int#
-> AVL e
-> Int#
-> e
-> AVL e
-> Int#
-> (# AVL e, Int# #)
u_ AVL e
l0 DECINT2(h0) e0 r0 DECINT1(h0) l1 DECINT1(h1) AVL e
e1 r1 DECINT2(h1)
u (Z AVL e
l0 e
e0 AVL e
r0) Int#
h0 (N AVL e
l1 e
e1 AVL e
r1) Int#
h1 = AVL e
-> Int#
-> e
-> AVL e
-> Int#
-> AVL e
-> Int#
-> e
-> AVL e
-> Int#
-> (# AVL e, Int# #)
u_ AVL e
l0 DECINT1(h0) e0 r0 DECINT1(h0) l1 DECINT2(h1) AVL e
e1 r1 DECINT1(h1)
u (Z AVL e
l0 e
e0 AVL e
r0) Int#
h0 (Z AVL e
l1 e
e1 AVL e
r1) Int#
h1 = AVL e
-> Int#
-> e
-> AVL e
-> Int#
-> AVL e
-> Int#
-> e
-> AVL e
-> Int#
-> (# AVL e, Int# #)
u_ AVL e
l0 DECINT1(h0) e0 r0 DECINT1(h0) l1 DECINT1(h1) AVL e
e1 r1 DECINT1(h1)
u (Z AVL e
l0 e
e0 AVL e
r0) Int#
h0 (P AVL e
l1 e
e1 AVL e
r1) Int#
h1 = AVL e
-> Int#
-> e
-> AVL e
-> Int#
-> AVL e
-> Int#
-> e
-> AVL e
-> Int#
-> (# AVL e, Int# #)
u_ AVL e
l0 DECINT1(h0) e0 r0 DECINT1(h0) l1 DECINT1(h1) AVL e
e1 r1 DECINT2(h1)
u (P AVL e
l0 e
e0 AVL e
r0) Int#
h0 (N AVL e
l1 e
e1 AVL e
r1) Int#
h1 = AVL e
-> Int#
-> e
-> AVL e
-> Int#
-> AVL e
-> Int#
-> e
-> AVL e
-> Int#
-> (# AVL e, Int# #)
u_ AVL e
l0 DECINT1(h0) e0 r0 DECINT2(h0) l1 DECINT2(h1) AVL e
e1 r1 DECINT1(h1)
u (P AVL e
l0 e
e0 AVL e
r0) Int#
h0 (Z AVL e
l1 e
e1 AVL e
r1) Int#
h1 = AVL e
-> Int#
-> e
-> AVL e
-> Int#
-> AVL e
-> Int#
-> e
-> AVL e
-> Int#
-> (# AVL e, Int# #)
u_ AVL e
l0 DECINT1(h0) e0 r0 DECINT2(h0) l1 DECINT1(h1) AVL e
e1 r1 DECINT1(h1)
u (P AVL e
l0 e
e0 AVL e
r0) Int#
h0 (P AVL e
l1 e
e1 AVL e
r1) Int#
h1 = AVL e
-> Int#
-> e
-> AVL e
-> Int#
-> AVL e
-> Int#
-> e
-> AVL e
-> Int#
-> (# AVL e, Int# #)
u_ AVL e
l0 DECINT1(h0) e0 r0 DECINT2(h0) l1 DECINT1(h1) AVL e
e1 r1 DECINT2(h1)
u_ :: AVL e
-> Int#
-> e
-> AVL e
-> Int#
-> AVL e
-> Int#
-> e
-> AVL e
-> Int#
-> (# AVL e, Int# #)
u_ AVL e
l0 Int#
hl0 e
e0 AVL e
r0 Int#
hr0 AVL e
l1 Int#
hl1 e
e1 AVL e
r1 Int#
hr1 =
case e -> e -> Ordering
c e
e0 e
e1 of
Ordering
LT -> case e -> AVL e -> Int# -> (# AVL e, Int#, Bool, AVL e, Int# #)
fork e
e1 AVL e
r0 Int#
hr0 of
UBT5(rl0,hrl0,be1,rr0,hrr0) -> case e -> AVL e -> Int# -> (# AVL e, Int#, Bool, AVL e, Int# #)
fork e
e0 AVL e
l1 Int#
hl1 of
UBT5(ll1,hll1,be0,lr1,hlr1) ->
case AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
u AVL e
l0 Int#
hl0 AVL e
ll1 Int#
hll1 of
UBT2(l,hl) -> case AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
u AVL e
rl0 Int#
hrl0 AVL e
lr1 Int#
hlr1 of
UBT2(m,hm) -> case AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
u AVL e
rr0 Int#
hrr0 AVL e
r1 Int#
hr1 of
UBT2(r,hr) -> case (if Bool
be1 then AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
forall e. AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
spliceH AVL e
m Int#
hm e
e1 AVL e
r Int#
hr
else AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
forall e. AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
joinH AVL e
m Int#
hm AVL e
r Int#
hr
) of
UBT2(t,ht) -> if Bool
be0 then AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
forall e. AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
spliceH AVL e
l Int#
hl e
e0 AVL e
t Int#
ht
else AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
forall e. AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
joinH AVL e
l Int#
hl AVL e
t Int#
ht
Ordering
EQ -> case AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
u AVL e
l0 Int#
hl0 AVL e
l1 Int#
hl1 of
UBT2(l,hl) -> case AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
u AVL e
r0 Int#
hr0 AVL e
r1 Int#
hr1 of
UBT2(r,hr) -> AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
forall e. AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
joinH AVL e
l Int#
hl AVL e
r Int#
hr
Ordering
GT -> case e -> AVL e -> Int# -> (# AVL e, Int#, Bool, AVL e, Int# #)
fork e
e0 AVL e
r1 Int#
hr1 of
UBT5(rl1,hrl1,be0,rr1,hrr1) -> case e -> AVL e -> Int# -> (# AVL e, Int#, Bool, AVL e, Int# #)
fork e
e1 AVL e
l0 Int#
hl0 of
UBT5(ll0,hll0,be1,lr0,hlr0) ->
case AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
u AVL e
ll0 Int#
hll0 AVL e
l1 Int#
hl1 of
UBT2(l,hl) -> case AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
u AVL e
lr0 Int#
hlr0 AVL e
rl1 Int#
hrl1 of
UBT2(m,hm) -> case AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
u AVL e
r0 Int#
hr0 AVL e
rr1 Int#
hrr1 of
UBT2(r,hr) -> case (if Bool
be1 then AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
forall e. AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
spliceH AVL e
l Int#
hl e
e1 AVL e
m Int#
hm
else AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
forall e. AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
joinH AVL e
l Int#
hl AVL e
m Int#
hm
) of
UBT2(t,ht) -> if Bool
be0 then AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
forall e. AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
spliceH AVL e
t Int#
ht e
e0 AVL e
r Int#
hr
else AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
forall e. AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
joinH AVL e
t Int#
ht AVL e
r Int#
hr
fork :: e -> AVL e -> Int# -> (# AVL e, Int#, Bool, AVL e, Int# #)
fork e
e0 AVL e
t1 Int#
ht1 = AVL e -> Int# -> (# AVL e, Int#, Bool, AVL e, Int# #)
fork_ AVL e
t1 Int#
ht1 where
fork_ :: AVL e -> Int# -> (# AVL e, Int#, Bool, AVL e, Int# #)
fork_ AVL e
E Int#
_ = UBT5(E, L(0), True, E, L(0))
fork_ (N AVL e
l e
e AVL e
r) Int#
h = AVL e
-> Int#
-> e
-> AVL e
-> Int#
-> (# AVL e, Int#, Bool, AVL e, Int# #)
fork__ AVL e
l DECINT2(h) e r DECINT1(h)
fork_ (Z AVL e
l e
e AVL e
r) Int#
h = AVL e
-> Int#
-> e
-> AVL e
-> Int#
-> (# AVL e, Int#, Bool, AVL e, Int# #)
fork__ AVL e
l DECINT1(h) e r DECINT1(h)
fork_ (P AVL e
l e
e AVL e
r) Int#
h = AVL e
-> Int#
-> e
-> AVL e
-> Int#
-> (# AVL e, Int#, Bool, AVL e, Int# #)
fork__ AVL e
l DECINT1(h) e r DECINT2(h)
fork__ :: AVL e
-> Int#
-> e
-> AVL e
-> Int#
-> (# AVL e, Int#, Bool, AVL e, Int# #)
fork__ AVL e
l Int#
hl e
e AVL e
r Int#
hr = case e -> e -> Ordering
c e
e0 e
e of
Ordering
LT -> case AVL e -> Int# -> (# AVL e, Int#, Bool, AVL e, Int# #)
fork_ AVL e
l Int#
hl of
UBT5(l0,hl0,be0,l1,hl1) -> case AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
forall e. AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
spliceH AVL e
l1 Int#
hl1 e
e AVL e
r Int#
hr of
UBT2(l1_,hl1_) -> UBT5(l0,hl0,be0,l1_,hl1_)
Ordering
EQ -> UBT5(l,hl,False,r,hr)
Ordering
GT -> case AVL e -> Int# -> (# AVL e, Int#, Bool, AVL e, Int# #)
fork_ AVL e
r Int#
hr of
UBT5(l0,hl0,be0,l1,hl1) -> case AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
forall e. AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
spliceH AVL e
l Int#
hl e
e AVL e
l0 Int#
hl0 of
UBT2(l0_,hl0_) -> UBT5(l0_,hl0_,be0,l1,hl1)
vennH :: (a -> b -> COrdering c) -> [c] -> UINT -> AVL a -> UINT -> AVL b -> UINT -> UBT6(AVL a,UINT,[c],UINT,AVL b,UINT)
vennH :: forall a b c.
(a -> b -> COrdering c)
-> [c]
-> Int#
-> AVL a
-> Int#
-> AVL b
-> Int#
-> (# AVL a, Int#, [c], Int#, AVL b, Int# #)
vennH a -> b -> COrdering c
cmp = [c]
-> Int#
-> AVL a
-> Int#
-> AVL b
-> Int#
-> (# AVL a, Int#, [c], Int#, AVL b, Int# #)
v where
v :: [c]
-> Int#
-> AVL a
-> Int#
-> AVL b
-> Int#
-> (# AVL a, Int#, [c], Int#, AVL b, Int# #)
v [c]
cs Int#
cl AVL a
E Int#
ha AVL b
tb Int#
hb = UBT6(E ,ha,cs,cl,tb,hb)
v [c]
cs Int#
cl AVL a
ta Int#
ha AVL b
E Int#
hb = UBT6(ta,ha,cs,cl,E ,hb)
v [c]
cs Int#
cl (N AVL a
la a
a AVL a
ra) Int#
ha (N AVL b
lb b
b AVL b
rb) Int#
hb = [c]
-> Int#
-> AVL a
-> Int#
-> a
-> AVL a
-> Int#
-> AVL b
-> Int#
-> b
-> AVL b
-> Int#
-> (# AVL a, Int#, [c], Int#, AVL b, Int# #)
v_ [c]
cs Int#
cl AVL a
la DECINT2(ha) a ra DECINT1(ha) lb DECINT2(hb) b rb DECINT1(hb)
v [c]
cs Int#
cl (N AVL a
la a
a AVL a
ra) Int#
ha (Z AVL b
lb b
b AVL b
rb) Int#
hb = [c]
-> Int#
-> AVL a
-> Int#
-> a
-> AVL a
-> Int#
-> AVL b
-> Int#
-> b
-> AVL b
-> Int#
-> (# AVL a, Int#, [c], Int#, AVL b, Int# #)
v_ [c]
cs Int#
cl AVL a
la DECINT2(ha) a ra DECINT1(ha) lb DECINT1(hb) b rb DECINT1(hb)
v [c]
cs Int#
cl (N AVL a
la a
a AVL a
ra) Int#
ha (P AVL b
lb b
b AVL b
rb) Int#
hb = [c]
-> Int#
-> AVL a
-> Int#
-> a
-> AVL a
-> Int#
-> AVL b
-> Int#
-> b
-> AVL b
-> Int#
-> (# AVL a, Int#, [c], Int#, AVL b, Int# #)
v_ [c]
cs Int#
cl AVL a
la DECINT2(ha) a ra DECINT1(ha) lb DECINT1(hb) b rb DECINT2(hb)
v [c]
cs Int#
cl (Z AVL a
la a
a AVL a
ra) Int#
ha (N AVL b
lb b
b AVL b
rb) Int#
hb = [c]
-> Int#
-> AVL a
-> Int#
-> a
-> AVL a
-> Int#
-> AVL b
-> Int#
-> b
-> AVL b
-> Int#
-> (# AVL a, Int#, [c], Int#, AVL b, Int# #)
v_ [c]
cs Int#
cl AVL a
la DECINT1(ha) a ra DECINT1(ha) lb DECINT2(hb) b rb DECINT1(hb)
v [c]
cs Int#
cl (Z AVL a
la a
a AVL a
ra) Int#
ha (Z AVL b
lb b
b AVL b
rb) Int#
hb = [c]
-> Int#
-> AVL a
-> Int#
-> a
-> AVL a
-> Int#
-> AVL b
-> Int#
-> b
-> AVL b
-> Int#
-> (# AVL a, Int#, [c], Int#, AVL b, Int# #)
v_ [c]
cs Int#
cl AVL a
la DECINT1(ha) a ra DECINT1(ha) lb DECINT1(hb) b rb DECINT1(hb)
v [c]
cs Int#
cl (Z AVL a
la a
a AVL a
ra) Int#
ha (P AVL b
lb b
b AVL b
rb) Int#
hb = [c]
-> Int#
-> AVL a
-> Int#
-> a
-> AVL a
-> Int#
-> AVL b
-> Int#
-> b
-> AVL b
-> Int#
-> (# AVL a, Int#, [c], Int#, AVL b, Int# #)
v_ [c]
cs Int#
cl AVL a
la DECINT1(ha) a ra DECINT1(ha) lb DECINT1(hb) b rb DECINT2(hb)
v [c]
cs Int#
cl (P AVL a
la a
a AVL a
ra) Int#
ha (N AVL b
lb b
b AVL b
rb) Int#
hb = [c]
-> Int#
-> AVL a
-> Int#
-> a
-> AVL a
-> Int#
-> AVL b
-> Int#
-> b
-> AVL b
-> Int#
-> (# AVL a, Int#, [c], Int#, AVL b, Int# #)
v_ [c]
cs Int#
cl AVL a
la DECINT1(ha) a ra DECINT2(ha) lb DECINT2(hb) b rb DECINT1(hb)
v [c]
cs Int#
cl (P AVL a
la a
a AVL a
ra) Int#
ha (Z AVL b
lb b
b AVL b
rb) Int#
hb = [c]
-> Int#
-> AVL a
-> Int#
-> a
-> AVL a
-> Int#
-> AVL b
-> Int#
-> b
-> AVL b
-> Int#
-> (# AVL a, Int#, [c], Int#, AVL b, Int# #)
v_ [c]
cs Int#
cl AVL a
la DECINT1(ha) a ra DECINT2(ha) lb DECINT1(hb) b rb DECINT1(hb)
v [c]
cs Int#
cl (P AVL a
la a
a AVL a
ra) Int#
ha (P AVL b
lb b
b AVL b
rb) Int#
hb = [c]
-> Int#
-> AVL a
-> Int#
-> a
-> AVL a
-> Int#
-> AVL b
-> Int#
-> b
-> AVL b
-> Int#
-> (# AVL a, Int#, [c], Int#, AVL b, Int# #)
v_ [c]
cs Int#
cl AVL a
la DECINT1(ha) a ra DECINT2(ha) lb DECINT1(hb) b rb DECINT2(hb)
v_ :: [c]
-> Int#
-> AVL a
-> Int#
-> a
-> AVL a
-> Int#
-> AVL b
-> Int#
-> b
-> AVL b
-> Int#
-> (# AVL a, Int#, [c], Int#, AVL b, Int# #)
v_ [c]
cs Int#
cl AVL a
la Int#
hla a
a AVL a
ra Int#
hra AVL b
lb Int#
hlb b
b AVL b
rb Int#
hrb =
case a -> b -> COrdering c
cmp a
a b
b of
COrdering c
Lt -> case (a -> b -> COrdering c)
-> a -> AVL b -> Int# -> (# AVL b, Int#, Maybe c, AVL b, Int# #)
forall a b c.
(a -> b -> COrdering c)
-> a -> AVL b -> Int# -> (# AVL b, Int#, Maybe c, AVL b, Int# #)
forka a -> b -> COrdering c
cmp a
a AVL b
lb Int#
hlb of
UBT5(llb,hllb,mbca,rlb,hrlb) -> case (a -> b -> COrdering c)
-> b -> AVL a -> Int# -> (# AVL a, Int#, Maybe c, AVL a, Int# #)
forall a b c.
(a -> b -> COrdering c)
-> b -> AVL a -> Int# -> (# AVL a, Int#, Maybe c, AVL a, Int# #)
forkb a -> b -> COrdering c
cmp b
b AVL a
ra Int#
hra of
UBT5(lra,hlra,mbcb,rra,hrra) ->
case [c]
-> Int#
-> AVL a
-> Int#
-> AVL b
-> Int#
-> (# AVL a, Int#, [c], Int#, AVL b, Int# #)
v [c]
cs Int#
cl AVL a
rra Int#
hrra AVL b
rb Int#
hrb of
UBT6(rab,hrab,cs0,cl0,rba,hrba) -> case (case Maybe c
mbcb of
Maybe c
Nothing -> case [c]
-> Int#
-> AVL a
-> Int#
-> AVL b
-> Int#
-> (# AVL a, Int#, [c], Int#, AVL b, Int# #)
v [c]
cs0 Int#
cl0 AVL a
lra Int#
hlra AVL b
rlb Int#
hrlb of
UBT6(mab,hmab,cs1,cl1,mba,hmba) -> case AVL b -> Int# -> b -> AVL b -> Int# -> (# AVL b, Int# #)
forall e. AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
spliceH AVL b
mba Int#
hmba b
b AVL b
rba Int#
hrba of
UBT2(mrba,hmrba) -> UBT6(mab,hmab,cs1,cl1,mrba,hmrba)
Just c
cb -> case [c]
-> Int#
-> AVL a
-> Int#
-> AVL b
-> Int#
-> (# AVL a, Int#, [c], Int#, AVL b, Int# #)
v (c
cbc -> [c] -> [c]
forall a. a -> [a] -> [a]
:[c]
cs0) INCINT1(cl0) lra hlra rlb hrlb of
UBT6(mab,hmab,cs1,cl1,mba,hmba) -> case AVL b -> Int# -> AVL b -> Int# -> (# AVL b, Int# #)
forall e. AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
joinH AVL b
mba Int#
hmba AVL b
rba Int#
hrba of
UBT2(mrba,hmrba) -> UBT6(mab,hmab,cs1,cl1,mrba,hmrba)
) of
UBT6(mab,hmab,cs1,cl1,mrba,hmrba) -> case AVL a -> Int# -> AVL a -> Int# -> (# AVL a, Int# #)
forall e. AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
joinH AVL a
mab Int#
hmab AVL a
rab Int#
hrab of
UBT2(mrab,hmrab) -> case (case Maybe c
mbca of
Maybe c
Nothing -> case [c]
-> Int#
-> AVL a
-> Int#
-> AVL b
-> Int#
-> (# AVL a, Int#, [c], Int#, AVL b, Int# #)
v [c]
cs1 Int#
cl1 AVL a
la Int#
hla AVL b
llb Int#
hllb of
UBT6(lab,hlab,cs2,cl2,lba,hlba) -> case AVL a -> Int# -> a -> AVL a -> Int# -> (# AVL a, Int# #)
forall e. AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
spliceH AVL a
lab Int#
hlab a
a AVL a
mrab Int#
hmrab of
UBT2(ab,hab) -> UBT6(ab,hab,cs2,cl2,lba,hlba)
Just c
ca -> case [c]
-> Int#
-> AVL a
-> Int#
-> AVL b
-> Int#
-> (# AVL a, Int#, [c], Int#, AVL b, Int# #)
v (c
cac -> [c] -> [c]
forall a. a -> [a] -> [a]
:[c]
cs1) INCINT1(cl1) la hla llb hllb of
UBT6(lab,hlab,cs2,cl2,lba,hlba) -> case AVL a -> Int# -> AVL a -> Int# -> (# AVL a, Int# #)
forall e. AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
joinH AVL a
lab Int#
hlab AVL a
mrab Int#
hmrab of
UBT2(ab,hab) -> UBT6(ab,hab,cs2,cl2,lba,hlba)
) of
UBT6(ab,hab,cs2,cl2,lba,hlba) -> case AVL b -> Int# -> AVL b -> Int# -> (# AVL b, Int# #)
forall e. AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
joinH AVL b
lba Int#
hlba AVL b
mrba Int#
hmrba of
UBT2(ba,hba) -> UBT6(ab,hab,cs2,cl2,ba,hba)
Eq c
c -> case [c]
-> Int#
-> AVL a
-> Int#
-> AVL b
-> Int#
-> (# AVL a, Int#, [c], Int#, AVL b, Int# #)
v [c]
cs Int#
cl AVL a
ra Int#
hra AVL b
rb Int#
hrb of
UBT6(rab,hrab,cs0,cl0,rba,hrba) -> case [c]
-> Int#
-> AVL a
-> Int#
-> AVL b
-> Int#
-> (# AVL a, Int#, [c], Int#, AVL b, Int# #)
v (c
cc -> [c] -> [c]
forall a. a -> [a] -> [a]
:[c]
cs0) INCINT1(cl0) la hla lb hlb of
UBT6(lab,hlab,cs1,cl1,lba,hlba) -> case AVL a -> Int# -> AVL a -> Int# -> (# AVL a, Int# #)
forall e. AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
joinH AVL a
lab Int#
hlab AVL a
rab Int#
hrab of
UBT2(ab,hab) -> case AVL b -> Int# -> AVL b -> Int# -> (# AVL b, Int# #)
forall e. AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
joinH AVL b
lba Int#
hlba AVL b
rba Int#
hrba of
UBT2(ba,hba) -> UBT6(ab,hab,cs1,cl1,ba,hba)
COrdering c
Gt -> case (a -> b -> COrdering c)
-> a -> AVL b -> Int# -> (# AVL b, Int#, Maybe c, AVL b, Int# #)
forall a b c.
(a -> b -> COrdering c)
-> a -> AVL b -> Int# -> (# AVL b, Int#, Maybe c, AVL b, Int# #)
forka a -> b -> COrdering c
cmp a
a AVL b
rb Int#
hrb of
UBT5(lrb,hlrb,mbca,rrb,hrrb) -> case (a -> b -> COrdering c)
-> b -> AVL a -> Int# -> (# AVL a, Int#, Maybe c, AVL a, Int# #)
forall a b c.
(a -> b -> COrdering c)
-> b -> AVL a -> Int# -> (# AVL a, Int#, Maybe c, AVL a, Int# #)
forkb a -> b -> COrdering c
cmp b
b AVL a
la Int#
hla of
UBT5(lla,hlla,mbcb,rla,hrla) ->
case [c]
-> Int#
-> AVL a
-> Int#
-> AVL b
-> Int#
-> (# AVL a, Int#, [c], Int#, AVL b, Int# #)
v [c]
cs Int#
cl AVL a
ra Int#
hra AVL b
rrb Int#
hrrb of
UBT6(rab,hrab,cs0,cl0,rba,hrba) -> case (case Maybe c
mbca of
Maybe c
Nothing -> case [c]
-> Int#
-> AVL a
-> Int#
-> AVL b
-> Int#
-> (# AVL a, Int#, [c], Int#, AVL b, Int# #)
v [c]
cs0 Int#
cl0 AVL a
rla Int#
hrla AVL b
lrb Int#
hlrb of
UBT6(mab,hmab,cs1,cl1,mba,hmba) -> case AVL a -> Int# -> a -> AVL a -> Int# -> (# AVL a, Int# #)
forall e. AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
spliceH AVL a
mab Int#
hmab a
a AVL a
rab Int#
hrab of
UBT2(mrab,hmrab) -> UBT6(mrab,hmrab,cs1,cl1,mba,hmba)
Just c
ca -> case [c]
-> Int#
-> AVL a
-> Int#
-> AVL b
-> Int#
-> (# AVL a, Int#, [c], Int#, AVL b, Int# #)
v (c
cac -> [c] -> [c]
forall a. a -> [a] -> [a]
:[c]
cs0) INCINT1(cl0) rla hrla lrb hlrb of
UBT6(mab,hmab,cs1,cl1,mba,hmba) -> case AVL a -> Int# -> AVL a -> Int# -> (# AVL a, Int# #)
forall e. AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
joinH AVL a
mab Int#
hmab AVL a
rab Int#
hrab of
UBT2(mrab,hmrab) -> UBT6(mrab,hmrab,cs1,cl1,mba,hmba)
) of
UBT6(mrab,hmrab,cs1,cl1,mba,hmba) -> case AVL b -> Int# -> AVL b -> Int# -> (# AVL b, Int# #)
forall e. AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
joinH AVL b
mba Int#
hmba AVL b
rba Int#
hrba of
UBT2(mrba,hmrba) -> case (case Maybe c
mbcb of
Maybe c
Nothing -> case [c]
-> Int#
-> AVL a
-> Int#
-> AVL b
-> Int#
-> (# AVL a, Int#, [c], Int#, AVL b, Int# #)
v [c]
cs1 Int#
cl1 AVL a
lla Int#
hlla AVL b
lb Int#
hlb of
UBT6(lab,hlab,cs2,cl2,lba,hlba) -> case AVL b -> Int# -> b -> AVL b -> Int# -> (# AVL b, Int# #)
forall e. AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
spliceH AVL b
lba Int#
hlba b
b AVL b
mrba Int#
hmrba of
UBT2(ba,hba) -> UBT6(lab,hlab,cs2,cl2,ba,hba)
Just c
cb -> case [c]
-> Int#
-> AVL a
-> Int#
-> AVL b
-> Int#
-> (# AVL a, Int#, [c], Int#, AVL b, Int# #)
v (c
cbc -> [c] -> [c]
forall a. a -> [a] -> [a]
:[c]
cs1) INCINT1(cl1) lla hlla lb hlb of
UBT6(lab,hlab,cs2,cl2,lba,hlba) -> case AVL b -> Int# -> AVL b -> Int# -> (# AVL b, Int# #)
forall e. AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
joinH AVL b
lba Int#
hlba AVL b
mrba Int#
hmrba of
UBT2(ba,hba) -> UBT6(lab,hlab,cs2,cl2,ba,hba)
) of
UBT6(lab,hlab,cs2,cl2,ba,hba) -> case AVL a -> Int# -> AVL a -> Int# -> (# AVL a, Int# #)
forall e. AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
joinH AVL a
lab Int#
hlab AVL a
mrab Int#
hmrab of
UBT2(ab,hab) -> UBT6(ab,hab,cs2,cl2,ba,hba)
vennMaybeH :: (a -> b -> COrdering (Maybe c)) -> [c] -> UINT -> AVL a -> UINT -> AVL b -> UINT -> UBT6(AVL a,UINT,[c],UINT,AVL b,UINT)
vennMaybeH :: forall a b c.
(a -> b -> COrdering (Maybe c))
-> [c]
-> Int#
-> AVL a
-> Int#
-> AVL b
-> Int#
-> (# AVL a, Int#, [c], Int#, AVL b, Int# #)
vennMaybeH a -> b -> COrdering (Maybe c)
cmp = [c]
-> Int#
-> AVL a
-> Int#
-> AVL b
-> Int#
-> (# AVL a, Int#, [c], Int#, AVL b, Int# #)
v where
v :: [c]
-> Int#
-> AVL a
-> Int#
-> AVL b
-> Int#
-> (# AVL a, Int#, [c], Int#, AVL b, Int# #)
v [c]
cs Int#
cl AVL a
E Int#
ha AVL b
tb Int#
hb = UBT6(E ,ha,cs,cl,tb,hb)
v [c]
cs Int#
cl AVL a
ta Int#
ha AVL b
E Int#
hb = UBT6(ta,ha,cs,cl,E ,hb)
v [c]
cs Int#
cl (N AVL a
la a
a AVL a
ra) Int#
ha (N AVL b
lb b
b AVL b
rb) Int#
hb = [c]
-> Int#
-> AVL a
-> Int#
-> a
-> AVL a
-> Int#
-> AVL b
-> Int#
-> b
-> AVL b
-> Int#
-> (# AVL a, Int#, [c], Int#, AVL b, Int# #)
v_ [c]
cs Int#
cl AVL a
la DECINT2(ha) a ra DECINT1(ha) lb DECINT2(hb) b rb DECINT1(hb)
v [c]
cs Int#
cl (N AVL a
la a
a AVL a
ra) Int#
ha (Z AVL b
lb b
b AVL b
rb) Int#
hb = [c]
-> Int#
-> AVL a
-> Int#
-> a
-> AVL a
-> Int#
-> AVL b
-> Int#
-> b
-> AVL b
-> Int#
-> (# AVL a, Int#, [c], Int#, AVL b, Int# #)
v_ [c]
cs Int#
cl AVL a
la DECINT2(ha) a ra DECINT1(ha) lb DECINT1(hb) b rb DECINT1(hb)
v [c]
cs Int#
cl (N AVL a
la a
a AVL a
ra) Int#
ha (P AVL b
lb b
b AVL b
rb) Int#
hb = [c]
-> Int#
-> AVL a
-> Int#
-> a
-> AVL a
-> Int#
-> AVL b
-> Int#
-> b
-> AVL b
-> Int#
-> (# AVL a, Int#, [c], Int#, AVL b, Int# #)
v_ [c]
cs Int#
cl AVL a
la DECINT2(ha) a ra DECINT1(ha) lb DECINT1(hb) b rb DECINT2(hb)
v [c]
cs Int#
cl (Z AVL a
la a
a AVL a
ra) Int#
ha (N AVL b
lb b
b AVL b
rb) Int#
hb = [c]
-> Int#
-> AVL a
-> Int#
-> a
-> AVL a
-> Int#
-> AVL b
-> Int#
-> b
-> AVL b
-> Int#
-> (# AVL a, Int#, [c], Int#, AVL b, Int# #)
v_ [c]
cs Int#
cl AVL a
la DECINT1(ha) a ra DECINT1(ha) lb DECINT2(hb) b rb DECINT1(hb)
v [c]
cs Int#
cl (Z AVL a
la a
a AVL a
ra) Int#
ha (Z AVL b
lb b
b AVL b
rb) Int#
hb = [c]
-> Int#
-> AVL a
-> Int#
-> a
-> AVL a
-> Int#
-> AVL b
-> Int#
-> b
-> AVL b
-> Int#
-> (# AVL a, Int#, [c], Int#, AVL b, Int# #)
v_ [c]
cs Int#
cl AVL a
la DECINT1(ha) a ra DECINT1(ha) lb DECINT1(hb) b rb DECINT1(hb)
v [c]
cs Int#
cl (Z AVL a
la a
a AVL a
ra) Int#
ha (P AVL b
lb b
b AVL b
rb) Int#
hb = [c]
-> Int#
-> AVL a
-> Int#
-> a
-> AVL a
-> Int#
-> AVL b
-> Int#
-> b
-> AVL b
-> Int#
-> (# AVL a, Int#, [c], Int#, AVL b, Int# #)
v_ [c]
cs Int#
cl AVL a
la DECINT1(ha) a ra DECINT1(ha) lb DECINT1(hb) b rb DECINT2(hb)
v [c]
cs Int#
cl (P AVL a
la a
a AVL a
ra) Int#
ha (N AVL b
lb b
b AVL b
rb) Int#
hb = [c]
-> Int#
-> AVL a
-> Int#
-> a
-> AVL a
-> Int#
-> AVL b
-> Int#
-> b
-> AVL b
-> Int#
-> (# AVL a, Int#, [c], Int#, AVL b, Int# #)
v_ [c]
cs Int#
cl AVL a
la DECINT1(ha) a ra DECINT2(ha) lb DECINT2(hb) b rb DECINT1(hb)
v [c]
cs Int#
cl (P AVL a
la a
a AVL a
ra) Int#
ha (Z AVL b
lb b
b AVL b
rb) Int#
hb = [c]
-> Int#
-> AVL a
-> Int#
-> a
-> AVL a
-> Int#
-> AVL b
-> Int#
-> b
-> AVL b
-> Int#
-> (# AVL a, Int#, [c], Int#, AVL b, Int# #)
v_ [c]
cs Int#
cl AVL a
la DECINT1(ha) a ra DECINT2(ha) lb DECINT1(hb) b rb DECINT1(hb)
v [c]
cs Int#
cl (P AVL a
la a
a AVL a
ra) Int#
ha (P AVL b
lb b
b AVL b
rb) Int#
hb = [c]
-> Int#
-> AVL a
-> Int#
-> a
-> AVL a
-> Int#
-> AVL b
-> Int#
-> b
-> AVL b
-> Int#
-> (# AVL a, Int#, [c], Int#, AVL b, Int# #)
v_ [c]
cs Int#
cl AVL a
la DECINT1(ha) a ra DECINT2(ha) lb DECINT1(hb) b rb DECINT2(hb)
v_ :: [c]
-> Int#
-> AVL a
-> Int#
-> a
-> AVL a
-> Int#
-> AVL b
-> Int#
-> b
-> AVL b
-> Int#
-> (# AVL a, Int#, [c], Int#, AVL b, Int# #)
v_ [c]
cs Int#
cl AVL a
la Int#
hla a
a AVL a
ra Int#
hra AVL b
lb Int#
hlb b
b AVL b
rb Int#
hrb =
case a -> b -> COrdering (Maybe c)
cmp a
a b
b of
COrdering (Maybe c)
Lt -> case (a -> b -> COrdering (Maybe c))
-> a
-> AVL b
-> Int#
-> (# AVL b, Int#, Maybe (Maybe c), AVL b, Int# #)
forall a b c.
(a -> b -> COrdering c)
-> a -> AVL b -> Int# -> (# AVL b, Int#, Maybe c, AVL b, Int# #)
forka a -> b -> COrdering (Maybe c)
cmp a
a AVL b
lb Int#
hlb of
UBT5(llb,hllb,mbmbca,rlb,hrlb) -> case (a -> b -> COrdering (Maybe c))
-> b
-> AVL a
-> Int#
-> (# AVL a, Int#, Maybe (Maybe c), AVL a, Int# #)
forall a b c.
(a -> b -> COrdering c)
-> b -> AVL a -> Int# -> (# AVL a, Int#, Maybe c, AVL a, Int# #)
forkb a -> b -> COrdering (Maybe c)
cmp b
b AVL a
ra Int#
hra of
UBT5(lra,hlra,mbmbcb,rra,hrra) ->
case [c]
-> Int#
-> AVL a
-> Int#
-> AVL b
-> Int#
-> (# AVL a, Int#, [c], Int#, AVL b, Int# #)
v [c]
cs Int#
cl AVL a
rra Int#
hrra AVL b
rb Int#
hrb of
UBT6(rab,hrab,cs0,cl0,rba,hrba) -> case (case Maybe (Maybe c)
mbmbcb of
Maybe (Maybe c)
Nothing -> case [c]
-> Int#
-> AVL a
-> Int#
-> AVL b
-> Int#
-> (# AVL a, Int#, [c], Int#, AVL b, Int# #)
v [c]
cs0 Int#
cl0 AVL a
lra Int#
hlra AVL b
rlb Int#
hrlb of
UBT6(mab,hmab,cs1,cl1,mba,hmba) -> case AVL b -> Int# -> b -> AVL b -> Int# -> (# AVL b, Int# #)
forall e. AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
spliceH AVL b
mba Int#
hmba b
b AVL b
rba Int#
hrba of
UBT2(mrba,hmrba) -> UBT6(mab,hmab,cs1,cl1,mrba,hmrba)
Just Maybe c
mbcb -> case (case Maybe c
mbcb of
Maybe c
Nothing -> [c]
-> Int#
-> AVL a
-> Int#
-> AVL b
-> Int#
-> (# AVL a, Int#, [c], Int#, AVL b, Int# #)
v [c]
cs0 Int#
cl0 AVL a
lra Int#
hlra AVL b
rlb Int#
hrlb
Just c
cb -> [c]
-> Int#
-> AVL a
-> Int#
-> AVL b
-> Int#
-> (# AVL a, Int#, [c], Int#, AVL b, Int# #)
v (c
cbc -> [c] -> [c]
forall a. a -> [a] -> [a]
:[c]
cs0) INCINT1(cl0) lra hlra rlb hrlb
) of
UBT6(mab,hmab,cs1,cl1,mba,hmba) -> case AVL b -> Int# -> AVL b -> Int# -> (# AVL b, Int# #)
forall e. AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
joinH AVL b
mba Int#
hmba AVL b
rba Int#
hrba of
UBT2(mrba,hmrba) -> UBT6(mab,hmab,cs1,cl1,mrba,hmrba)
) of
UBT6(mab,hmab,cs1,cl1,mrba,hmrba) -> case AVL a -> Int# -> AVL a -> Int# -> (# AVL a, Int# #)
forall e. AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
joinH AVL a
mab Int#
hmab AVL a
rab Int#
hrab of
UBT2(mrab,hmrab) -> case (case Maybe (Maybe c)
mbmbca of
Maybe (Maybe c)
Nothing -> case [c]
-> Int#
-> AVL a
-> Int#
-> AVL b
-> Int#
-> (# AVL a, Int#, [c], Int#, AVL b, Int# #)
v [c]
cs1 Int#
cl1 AVL a
la Int#
hla AVL b
llb Int#
hllb of
UBT6(lab,hlab,cs2,cl2,lba,hlba) -> case AVL a -> Int# -> a -> AVL a -> Int# -> (# AVL a, Int# #)
forall e. AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
spliceH AVL a
lab Int#
hlab a
a AVL a
mrab Int#
hmrab of
UBT2(ab,hab) -> UBT6(ab,hab,cs2,cl2,lba,hlba)
Just Maybe c
mbca -> case (case Maybe c
mbca of
Maybe c
Nothing -> [c]
-> Int#
-> AVL a
-> Int#
-> AVL b
-> Int#
-> (# AVL a, Int#, [c], Int#, AVL b, Int# #)
v [c]
cs1 Int#
cl1 AVL a
la Int#
hla AVL b
llb Int#
hllb
Just c
ca -> [c]
-> Int#
-> AVL a
-> Int#
-> AVL b
-> Int#
-> (# AVL a, Int#, [c], Int#, AVL b, Int# #)
v (c
cac -> [c] -> [c]
forall a. a -> [a] -> [a]
:[c]
cs1) INCINT1(cl1) la hla llb hllb
) of
UBT6(lab,hlab,cs2,cl2,lba,hlba) -> case AVL a -> Int# -> AVL a -> Int# -> (# AVL a, Int# #)
forall e. AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
joinH AVL a
lab Int#
hlab AVL a
mrab Int#
hmrab of
UBT2(ab,hab) -> UBT6(ab,hab,cs2,cl2,lba,hlba)
) of
UBT6(ab,hab,cs2,cl2,lba,hlba) -> case AVL b -> Int# -> AVL b -> Int# -> (# AVL b, Int# #)
forall e. AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
joinH AVL b
lba Int#
hlba AVL b
mrba Int#
hmrba of
UBT2(ba,hba) -> UBT6(ab,hab,cs2,cl2,ba,hba)
Eq Maybe c
mbc -> case [c]
-> Int#
-> AVL a
-> Int#
-> AVL b
-> Int#
-> (# AVL a, Int#, [c], Int#, AVL b, Int# #)
v [c]
cs Int#
cl AVL a
ra Int#
hra AVL b
rb Int#
hrb of
UBT6(rab,hrab,cs0,cl0,rba,hrba) -> case (case Maybe c
mbc of
Maybe c
Nothing -> [c]
-> Int#
-> AVL a
-> Int#
-> AVL b
-> Int#
-> (# AVL a, Int#, [c], Int#, AVL b, Int# #)
v [c]
cs0 Int#
cl0 AVL a
la Int#
hla AVL b
lb Int#
hlb
Just c
c -> [c]
-> Int#
-> AVL a
-> Int#
-> AVL b
-> Int#
-> (# AVL a, Int#, [c], Int#, AVL b, Int# #)
v (c
cc -> [c] -> [c]
forall a. a -> [a] -> [a]
:[c]
cs0) INCINT1(cl0) la hla lb hlb
) of
UBT6(lab,hlab,cs1,cl1,lba,hlba) -> case AVL a -> Int# -> AVL a -> Int# -> (# AVL a, Int# #)
forall e. AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
joinH AVL a
lab Int#
hlab AVL a
rab Int#
hrab of
UBT2(ab,hab) -> case AVL b -> Int# -> AVL b -> Int# -> (# AVL b, Int# #)
forall e. AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
joinH AVL b
lba Int#
hlba AVL b
rba Int#
hrba of
UBT2(ba,hba) -> UBT6(ab,hab,cs1,cl1,ba,hba)
COrdering (Maybe c)
Gt -> case (a -> b -> COrdering (Maybe c))
-> a
-> AVL b
-> Int#
-> (# AVL b, Int#, Maybe (Maybe c), AVL b, Int# #)
forall a b c.
(a -> b -> COrdering c)
-> a -> AVL b -> Int# -> (# AVL b, Int#, Maybe c, AVL b, Int# #)
forka a -> b -> COrdering (Maybe c)
cmp a
a AVL b
rb Int#
hrb of
UBT5(lrb,hlrb,mbmbca,rrb,hrrb) -> case (a -> b -> COrdering (Maybe c))
-> b
-> AVL a
-> Int#
-> (# AVL a, Int#, Maybe (Maybe c), AVL a, Int# #)
forall a b c.
(a -> b -> COrdering c)
-> b -> AVL a -> Int# -> (# AVL a, Int#, Maybe c, AVL a, Int# #)
forkb a -> b -> COrdering (Maybe c)
cmp b
b AVL a
la Int#
hla of
UBT5(lla,hlla,mbmbcb,rla,hrla) ->
case [c]
-> Int#
-> AVL a
-> Int#
-> AVL b
-> Int#
-> (# AVL a, Int#, [c], Int#, AVL b, Int# #)
v [c]
cs Int#
cl AVL a
ra Int#
hra AVL b
rrb Int#
hrrb of
UBT6(rab,hrab,cs0,cl0,rba,hrba) -> case (case Maybe (Maybe c)
mbmbca of
Maybe (Maybe c)
Nothing -> case [c]
-> Int#
-> AVL a
-> Int#
-> AVL b
-> Int#
-> (# AVL a, Int#, [c], Int#, AVL b, Int# #)
v [c]
cs0 Int#
cl0 AVL a
rla Int#
hrla AVL b
lrb Int#
hlrb of
UBT6(mab,hmab,cs1,cl1,mba,hmba) -> case AVL a -> Int# -> a -> AVL a -> Int# -> (# AVL a, Int# #)
forall e. AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
spliceH AVL a
mab Int#
hmab a
a AVL a
rab Int#
hrab of
UBT2(mrab,hmrab) -> UBT6(mrab,hmrab,cs1,cl1,mba,hmba)
Just Maybe c
mbca -> case (case Maybe c
mbca of
Maybe c
Nothing -> [c]
-> Int#
-> AVL a
-> Int#
-> AVL b
-> Int#
-> (# AVL a, Int#, [c], Int#, AVL b, Int# #)
v [c]
cs0 Int#
cl0 AVL a
rla Int#
hrla AVL b
lrb Int#
hlrb
Just c
ca -> [c]
-> Int#
-> AVL a
-> Int#
-> AVL b
-> Int#
-> (# AVL a, Int#, [c], Int#, AVL b, Int# #)
v (c
cac -> [c] -> [c]
forall a. a -> [a] -> [a]
:[c]
cs0) INCINT1(cl0) rla hrla lrb hlrb
) of
UBT6(mab,hmab,cs1,cl1,mba,hmba) -> case AVL a -> Int# -> AVL a -> Int# -> (# AVL a, Int# #)
forall e. AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
joinH AVL a
mab Int#
hmab AVL a
rab Int#
hrab of
UBT2(mrab,hmrab) -> UBT6(mrab,hmrab,cs1,cl1,mba,hmba)
) of
UBT6(mrab,hmrab,cs1,cl1,mba,hmba) -> case AVL b -> Int# -> AVL b -> Int# -> (# AVL b, Int# #)
forall e. AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
joinH AVL b
mba Int#
hmba AVL b
rba Int#
hrba of
UBT2(mrba,hmrba) -> case (case Maybe (Maybe c)
mbmbcb of
Maybe (Maybe c)
Nothing -> case [c]
-> Int#
-> AVL a
-> Int#
-> AVL b
-> Int#
-> (# AVL a, Int#, [c], Int#, AVL b, Int# #)
v [c]
cs1 Int#
cl1 AVL a
lla Int#
hlla AVL b
lb Int#
hlb of
UBT6(lab,hlab,cs2,cl2,lba,hlba) -> case AVL b -> Int# -> b -> AVL b -> Int# -> (# AVL b, Int# #)
forall e. AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
spliceH AVL b
lba Int#
hlba b
b AVL b
mrba Int#
hmrba of
UBT2(ba,hba) -> UBT6(lab,hlab,cs2,cl2,ba,hba)
Just Maybe c
mbcb -> case (case Maybe c
mbcb of
Maybe c
Nothing -> [c]
-> Int#
-> AVL a
-> Int#
-> AVL b
-> Int#
-> (# AVL a, Int#, [c], Int#, AVL b, Int# #)
v [c]
cs1 Int#
cl1 AVL a
lla Int#
hlla AVL b
lb Int#
hlb
Just c
cb -> [c]
-> Int#
-> AVL a
-> Int#
-> AVL b
-> Int#
-> (# AVL a, Int#, [c], Int#, AVL b, Int# #)
v (c
cbc -> [c] -> [c]
forall a. a -> [a] -> [a]
:[c]
cs1) INCINT1(cl1) lla hlla lb hlb
) of
UBT6(lab,hlab,cs2,cl2,lba,hlba) -> case AVL b -> Int# -> AVL b -> Int# -> (# AVL b, Int# #)
forall e. AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
joinH AVL b
lba Int#
hlba AVL b
mrba Int#
hmrba of
UBT2(ba,hba) -> UBT6(lab,hlab,cs2,cl2,ba,hba)
) of
UBT6(lab,hlab,cs2,cl2,ba,hba) -> case AVL a -> Int# -> AVL a -> Int# -> (# AVL a, Int# #)
forall e. AVL e -> Int# -> AVL e -> Int# -> (# AVL e, Int# #)
joinH AVL a
lab Int#
hlab AVL a
mrab Int#
hmrab of
UBT2(ab,hab) -> UBT6(ab,hab,cs2,cl2,ba,hba)
forka :: (a -> b -> COrdering c) -> a -> AVL b -> UINT -> UBT5(AVL b,UINT,Maybe c,AVL b,UINT)
forka :: forall a b c.
(a -> b -> COrdering c)
-> a -> AVL b -> Int# -> (# AVL b, Int#, Maybe c, AVL b, Int# #)
forka a -> b -> COrdering c
cmp a
a AVL b
tb Int#
htb = AVL b -> Int# -> (# AVL b, Int#, Maybe c, AVL b, Int# #)
f AVL b
tb Int#
htb where
f :: AVL b -> Int# -> (# AVL b, Int#, Maybe c, AVL b, Int# #)
f AVL b
E Int#
_ = UBT5(E,L(0),Nothing,E,L(0))
f n :: AVL b
n@(N AVL b
_ b
b AVL b
r) L(2) = case cmp a b of
COrdering c
Lt -> UBT5(E,L(0),Nothing,n,L(2))
Eq c
c -> UBT5(E,L(0),Just c ,r,L(1))
COrdering c
Gt -> case AVL b
r of
Z AVL b
_ b
br AVL b
_ -> case a -> b -> COrdering c
cmp a
a b
br of
COrdering c
Lt -> UBT5(Z E b E,L(1),Nothing,r,L(1))
Eq c
c -> UBT5(Z E b E,L(1),Just c ,E,L(0))
COrdering c
Gt -> UBT5(n ,L(2),Nothing,E,L(0))
AVL b
_ -> Any
forall a. HasCallStack => a
undefined Any
-> (# AVL b, Int#, Maybe c, AVL b, Int# #)
-> (# AVL b, Int#, Maybe c, AVL b, Int# #)
forall a b. a -> b -> b
`seq` UBT5(E,L(0),Nothing,E,L(0))
f (N AVL b
l b
b AVL b
r) Int#
h = AVL b
-> Int#
-> b
-> AVL b
-> Int#
-> (# AVL b, Int#, Maybe c, AVL b, Int# #)
f_ AVL b
l DECINT2(h) b r DECINT1(h)
f z :: AVL b
z@(Z AVL b
l b
b AVL b
r) L(2) = case cmp a b of
COrdering c
Lt -> case AVL b
l of
Z AVL b
_ b
bl AVL b
_ -> case a -> b -> COrdering c
cmp a
a b
bl of
COrdering c
Lt -> UBT5(E,L(0),Nothing,z ,L(2))
Eq c
c -> UBT5(E,L(0),Just c ,b
N AVL b
E b r,L(2))
COrdering c
Gt -> UBT5(l,L(1),Nothing,N E b r,L(2))
AVL b
_ -> Any
forall a. HasCallStack => a
undefined Any
-> (# AVL b, Int#, Maybe c, AVL b, Int# #)
-> (# AVL b, Int#, Maybe c, AVL b, Int# #)
forall a b. a -> b -> b
`seq` UBT5(E,L(0),Nothing,E,L(0))
Eq c
c -> UBT5(l,L(1),Just c,r,L(1))
COrdering c
Gt -> case AVL b
r of
Z AVL b
_ b
br AVL b
_ -> case a -> b -> COrdering c
cmp a
a b
br of
COrdering c
Lt -> UBT5(P l b E,L(2),Nothing,r,L(1))
Eq c
c -> UBT5(P l b E,L(2),Just c ,E,L(0))
COrdering c
Gt -> UBT5(z ,L(2),Nothing,E,L(0))
AVL b
_ -> Any
forall a. HasCallStack => a
undefined Any
-> (# AVL b, Int#, Maybe c, AVL b, Int# #)
-> (# AVL b, Int#, Maybe c, AVL b, Int# #)
forall a b. a -> b -> b
`seq` UBT5(E,L(0),Nothing,E,L(0))
f z :: AVL b
z@(Z AVL b
_ b
b AVL b
_) L(1) = case cmp a b of
COrdering c
Lt -> UBT5(E,L(0),Nothing,z,L(1))
Eq c
c -> UBT5(E,L(0),Just c ,E,L(0))
COrdering c
Gt -> UBT5(z,L(1),Nothing,E,L(0))
f (Z AVL b
l b
b AVL b
r) Int#
h = AVL b
-> Int#
-> b
-> AVL b
-> Int#
-> (# AVL b, Int#, Maybe c, AVL b, Int# #)
f_ AVL b
l DECINT1(h) b r DECINT1(h)
f p :: AVL b
p@(P AVL b
l b
b AVL b
_) L(2) = case cmp a b of
COrdering c
Lt -> case AVL b
l of
Z AVL b
_ b
bl AVL b
_ -> case a -> b -> COrdering c
cmp a
a b
bl of
COrdering c
Lt -> UBT5(E,L(0),Nothing,p ,L(2))
Eq c
c -> UBT5(E,L(0),Just c ,b
Z AVL b
forall e. AVL e
E b E,L(1))
COrdering c
Gt -> UBT5(l,L(1),Nothing,Z E b E,L(1))
AVL b
_ -> Any
forall a. HasCallStack => a
undefined Any
-> (# AVL b, Int#, Maybe c, AVL b, Int# #)
-> (# AVL b, Int#, Maybe c, AVL b, Int# #)
forall a b. a -> b -> b
`seq` UBT5(E,L(0),Nothing,E,L(0))
Eq c
c -> UBT5(l,L(1),Just c ,E,L(0))
COrdering c
Gt -> UBT5(p,L(2),Nothing,E,L(0))
f (P AVL b
l b
b AVL b
r) Int#
h = AVL b
-> Int#
-> b
-> AVL b
-> Int#
-> (# AVL b, Int#, Maybe c, AVL b, Int# #)
f_ AVL b
l DECINT1(h) b r DECINT2(h)
f_ :: AVL b
-> Int#
-> b
-> AVL b
-> Int#
-> (# AVL b, Int#, Maybe c, AVL b, Int# #)
f_ AVL b
l Int#
hl b
b AVL b
r Int#
hr = case a -> b -> COrdering c
cmp a
a b
b of
COrdering c
Lt -> case AVL b -> Int# -> (# AVL b, Int#, Maybe c, AVL b, Int# #)
f AVL b
l Int#
hl of
UBT5(ll,hll,mbc,lr,hlr) -> case AVL b -> Int# -> b -> AVL b -> Int# -> (# AVL b, Int# #)
forall e. AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
spliceH AVL b
lr Int#
hlr b
b AVL b
r Int#
hr of
UBT2(r_,hr_) -> UBT5(ll,hll,mbc,r_,hr_)
Eq c
c -> UBT5(l,hl,Just AVL b
c,r,hr)
COrdering c
Gt -> case AVL b -> Int# -> (# AVL b, Int#, Maybe c, AVL b, Int# #)
f AVL b
r Int#
hr of
UBT5(rl,hrl,mbc,rr,hrr) -> case AVL b -> Int# -> b -> AVL b -> Int# -> (# AVL b, Int# #)
forall e. AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
spliceH AVL b
l Int#
hl b
b AVL b
rl Int#
hrl of
UBT2(l_,hl_) -> UBT5(l_,hl_,mbc,rr,hrr)
forkb :: (a -> b -> COrdering c) -> b -> AVL a -> UINT -> UBT5(AVL a,UINT,Maybe c,AVL a,UINT)
forkb :: forall a b c.
(a -> b -> COrdering c)
-> b -> AVL a -> Int# -> (# AVL a, Int#, Maybe c, AVL a, Int# #)
forkb a -> b -> COrdering c
cmp b
b AVL a
ta Int#
hta = AVL a -> Int# -> (# AVL a, Int#, Maybe c, AVL a, Int# #)
f AVL a
ta Int#
hta where
f :: AVL a -> Int# -> (# AVL a, Int#, Maybe c, AVL a, Int# #)
f AVL a
E Int#
_ = UBT5(E,L(0),Nothing,E,L(0))
f n :: AVL a
n@(N AVL a
_ a
a AVL a
r) L(2) = case cmp a b of
COrdering c
Gt -> UBT5(E,L(0),Nothing,n,L(2))
Eq c
c -> UBT5(E,L(0),Just c ,r,L(1))
COrdering c
Lt -> case AVL a
r of
Z AVL a
_ a
ar AVL a
_ -> case a -> b -> COrdering c
cmp a
ar b
b of
COrdering c
Gt -> UBT5(Z E a E,L(1),Nothing,r,L(1))
Eq c
c -> UBT5(Z E a E,L(1),Just c ,E,L(0))
COrdering c
Lt -> UBT5(n ,L(2),Nothing,E,L(0))
AVL a
_ -> Any
forall a. HasCallStack => a
undefined Any
-> (# AVL a, Int#, Maybe c, AVL a, Int# #)
-> (# AVL a, Int#, Maybe c, AVL a, Int# #)
forall a b. a -> b -> b
`seq` UBT5(E,L(0),Nothing,E,L(0))
f (N AVL a
l a
a AVL a
r) Int#
h = AVL a
-> Int#
-> a
-> AVL a
-> Int#
-> (# AVL a, Int#, Maybe c, AVL a, Int# #)
f_ AVL a
l DECINT2(h) a r DECINT1(h)
f z :: AVL a
z@(Z AVL a
l a
a AVL a
r) L(2) = case cmp a b of
COrdering c
Gt -> case AVL a
l of
Z AVL a
_ a
al AVL a
_ -> case a -> b -> COrdering c
cmp a
al b
b of
COrdering c
Gt -> UBT5(E,L(0),Nothing,z ,L(2))
Eq c
c -> UBT5(E,L(0),Just c ,a
N AVL a
E a r,L(2))
COrdering c
Lt -> UBT5(l,L(1),Nothing,N E a r,L(2))
AVL a
_ -> Any
forall a. HasCallStack => a
undefined Any
-> (# AVL a, Int#, Maybe c, AVL a, Int# #)
-> (# AVL a, Int#, Maybe c, AVL a, Int# #)
forall a b. a -> b -> b
`seq` UBT5(E,L(0),Nothing,E,L(0))
Eq c
c -> UBT5(l,L(1),Just c,r,L(1))
COrdering c
Lt -> case AVL a
r of
Z AVL a
_ a
ar AVL a
_ -> case a -> b -> COrdering c
cmp a
ar b
b of
COrdering c
Gt -> UBT5(P l a E,L(2),Nothing,r,L(1))
Eq c
c -> UBT5(P l a E,L(2),Just c ,E,L(0))
COrdering c
Lt -> UBT5(z ,L(2),Nothing,E,L(0))
AVL a
_ -> Any
forall a. HasCallStack => a
undefined Any
-> (# AVL a, Int#, Maybe c, AVL a, Int# #)
-> (# AVL a, Int#, Maybe c, AVL a, Int# #)
forall a b. a -> b -> b
`seq` UBT5(E,L(0),Nothing,E,L(0))
f z :: AVL a
z@(Z AVL a
_ a
a AVL a
_) L(1) = case cmp a b of
COrdering c
Gt -> UBT5(E,L(0),Nothing,z,L(1))
Eq c
c -> UBT5(E,L(0),Just c ,E,L(0))
COrdering c
Lt -> UBT5(z,L(1),Nothing,E,L(0))
f (Z AVL a
l a
a AVL a
r) Int#
h = AVL a
-> Int#
-> a
-> AVL a
-> Int#
-> (# AVL a, Int#, Maybe c, AVL a, Int# #)
f_ AVL a
l DECINT1(h) a r DECINT1(h)
f p :: AVL a
p@(P AVL a
l a
a AVL a
_) L(2) = case cmp a b of
COrdering c
Gt -> case AVL a
l of
Z AVL a
_ a
al AVL a
_ -> case a -> b -> COrdering c
cmp a
al b
b of
COrdering c
Gt -> UBT5(E,L(0),Nothing,p ,L(2))
Eq c
c -> UBT5(E,L(0),Just c ,a
Z AVL a
forall e. AVL e
E a E,L(1))
COrdering c
Lt -> UBT5(l,L(1),Nothing,Z E a E,L(1))
AVL a
_ -> Any
forall a. HasCallStack => a
undefined Any
-> (# AVL a, Int#, Maybe c, AVL a, Int# #)
-> (# AVL a, Int#, Maybe c, AVL a, Int# #)
forall a b. a -> b -> b
`seq` UBT5(E,L(0),Nothing,E,L(0))
Eq c
c -> UBT5(l,L(1),Just c ,E,L(0))
COrdering c
Lt -> UBT5(p,L(2),Nothing,E,L(0))
f (P AVL a
l a
a AVL a
r) Int#
h = AVL a
-> Int#
-> a
-> AVL a
-> Int#
-> (# AVL a, Int#, Maybe c, AVL a, Int# #)
f_ AVL a
l DECINT1(h) a r DECINT2(h)
f_ :: AVL a
-> Int#
-> a
-> AVL a
-> Int#
-> (# AVL a, Int#, Maybe c, AVL a, Int# #)
f_ AVL a
l Int#
hl a
a AVL a
r Int#
hr = case a -> b -> COrdering c
cmp a
a b
b of
COrdering c
Gt -> case AVL a -> Int# -> (# AVL a, Int#, Maybe c, AVL a, Int# #)
f AVL a
l Int#
hl of
UBT5(ll,hll,mbc,lr,hlr) -> case AVL a -> Int# -> a -> AVL a -> Int# -> (# AVL a, Int# #)
forall e. AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
spliceH AVL a
lr Int#
hlr a
a AVL a
r Int#
hr of
UBT2(r_,hr_) -> UBT5(ll,hll,mbc,r_,hr_)
Eq c
c -> UBT5(l,hl,Just AVL a
c,r,hr)
COrdering c
Lt -> case AVL a -> Int# -> (# AVL a, Int#, Maybe c, AVL a, Int# #)
f AVL a
r Int#
hr of
UBT5(rl,hrl,mbc,rr,hrr) -> case AVL a -> Int# -> a -> AVL a -> Int# -> (# AVL a, Int# #)
forall e. AVL e -> Int# -> e -> AVL e -> Int# -> (# AVL e, Int# #)
spliceH AVL a
l Int#
hl a
a AVL a
rl Int#
hrl of
UBT2(l_,hl_) -> UBT5(l_,hl_,mbc,rr,hrr)