module Data.Tree.AVL.Test.Utils
(
isBalanced,isSorted,isSortedOK,
minElements,maxElements,
) where
import Data.Tree.AVL.Internals.Types(AVL(..))
import GHC.Base
#include "ghcdefs.h"
isBalanced :: AVL e -> Bool
isBalanced :: forall e. AVL e -> Bool
isBalanced AVL e
t = Bool -> Bool
not (Int# -> Bool
isTrue# (AVL e -> Int#
forall e. AVL e -> Int#
cH AVL e
t Int# -> Int# -> Int#
EQL L(-1)))
cH :: AVL e -> UINT
cH :: forall e. AVL e -> Int#
cH AVL e
E = L(0)
cH (N AVL e
l e
_ AVL e
r) = Int# -> AVL e -> AVL e -> Int#
forall e. Int# -> AVL e -> AVL e -> Int#
cH_ L(1AVL e
) AVL e
l r
cH (Z AVL e
l e
_ AVL e
r) = Int# -> AVL e -> AVL e -> Int#
forall e. Int# -> AVL e -> AVL e -> Int#
cH_ L(0AVL e
) AVL e
l r
cH (P AVL e
l e
_ AVL e
r) = Int# -> AVL e -> AVL e -> Int#
forall e. Int# -> AVL e -> AVL e -> Int#
cH_ L(1AVL e
) AVL e
r l
cH_ :: UINT -> AVL e -> AVL e -> UINT
cH_ :: forall e. Int# -> AVL e -> AVL e -> Int#
cH_ Int#
delta AVL e
l AVL e
r = let hl :: Int#
hl = AVL e -> Int#
forall e. AVL e -> Int#
cH AVL e
l
in if Int# -> Bool
isTrue# (Int#
hl Int# -> Int# -> Int#
EQL L(-1)) then hl
else let hr :: Int#
hr = AVL e -> Int#
forall e. AVL e -> Int#
cH AVL e
r
in if Int# -> Bool
isTrue# (Int#
hr Int# -> Int# -> Int#
EQL L(-1)) then hr
else if Int# -> Bool
isTrue# (SUBINT(hr,hl) EQL delta) then INCINT1(hr)
else L(-1)
isSorted :: (e -> e -> Ordering) -> AVL e -> Bool
isSorted :: forall e. (e -> e -> Ordering) -> AVL e -> Bool
isSorted e -> e -> Ordering
c = AVL e -> Bool
isSorted' where
isSorted' :: AVL e -> Bool
isSorted' AVL e
E = Bool
True
isSorted' (N AVL e
l e
e AVL e
r) = AVL e -> e -> AVL e -> Bool
isSorted'' AVL e
l e
e AVL e
r
isSorted' (Z AVL e
l e
e AVL e
r) = AVL e -> e -> AVL e -> Bool
isSorted'' AVL e
l e
e AVL e
r
isSorted' (P AVL e
l e
e AVL e
r) = AVL e -> e -> AVL e -> Bool
isSorted'' AVL e
l e
e AVL e
r
isSorted'' :: AVL e -> e -> AVL e -> Bool
isSorted'' AVL e
l e
e AVL e
r = (AVL e -> e -> Bool
isSortedU AVL e
l e
e) Bool -> Bool -> Bool
&& (e -> AVL e -> Bool
isSortedL e
e AVL e
r)
isSortedU :: AVL e -> e -> Bool
isSortedU AVL e
E e
_ = Bool
True
isSortedU (N AVL e
l e
e AVL e
r) e
ul = AVL e -> e -> AVL e -> e -> Bool
isSortedU' AVL e
l e
e AVL e
r e
ul
isSortedU (Z AVL e
l e
e AVL e
r) e
ul = AVL e -> e -> AVL e -> e -> Bool
isSortedU' AVL e
l e
e AVL e
r e
ul
isSortedU (P AVL e
l e
e AVL e
r) e
ul = AVL e -> e -> AVL e -> e -> Bool
isSortedU' AVL e
l e
e AVL e
r e
ul
isSortedU' :: AVL e -> e -> AVL e -> e -> Bool
isSortedU' AVL e
l e
e AVL e
r e
ul = case e -> e -> Ordering
c e
e e
ul of
Ordering
LT -> (AVL e -> e -> Bool
isSortedU AVL e
l e
e) Bool -> Bool -> Bool
&& (e -> AVL e -> e -> Bool
isSortedLU e
e AVL e
r e
ul)
Ordering
_ -> Bool
False
isSortedL :: e -> AVL e -> Bool
isSortedL e
_ AVL e
E = Bool
True
isSortedL e
ll (N AVL e
l e
e AVL e
r) = e -> AVL e -> e -> AVL e -> Bool
isSortedL' e
ll AVL e
l e
e AVL e
r
isSortedL e
ll (Z AVL e
l e
e AVL e
r) = e -> AVL e -> e -> AVL e -> Bool
isSortedL' e
ll AVL e
l e
e AVL e
r
isSortedL e
ll (P AVL e
l e
e AVL e
r) = e -> AVL e -> e -> AVL e -> Bool
isSortedL' e
ll AVL e
l e
e AVL e
r
isSortedL' :: e -> AVL e -> e -> AVL e -> Bool
isSortedL' e
ll AVL e
l e
e AVL e
r = case e -> e -> Ordering
c e
e e
ll of
Ordering
GT -> (e -> AVL e -> e -> Bool
isSortedLU e
ll AVL e
l e
e) Bool -> Bool -> Bool
&& (e -> AVL e -> Bool
isSortedL e
e AVL e
r)
Ordering
_ -> Bool
False
isSortedLU :: e -> AVL e -> e -> Bool
isSortedLU e
_ AVL e
E e
_ = Bool
True
isSortedLU e
ll (N AVL e
l e
e AVL e
r) e
ul = e -> AVL e -> e -> AVL e -> e -> Bool
isSortedLU' e
ll AVL e
l e
e AVL e
r e
ul
isSortedLU e
ll (Z AVL e
l e
e AVL e
r) e
ul = e -> AVL e -> e -> AVL e -> e -> Bool
isSortedLU' e
ll AVL e
l e
e AVL e
r e
ul
isSortedLU e
ll (P AVL e
l e
e AVL e
r) e
ul = e -> AVL e -> e -> AVL e -> e -> Bool
isSortedLU' e
ll AVL e
l e
e AVL e
r e
ul
isSortedLU' :: e -> AVL e -> e -> AVL e -> e -> Bool
isSortedLU' e
ll AVL e
l e
e AVL e
r e
ul = case e -> e -> Ordering
c e
e e
ll of
Ordering
GT -> case e -> e -> Ordering
c e
e e
ul of
Ordering
LT -> (e -> AVL e -> e -> Bool
isSortedLU e
ll AVL e
l e
e) Bool -> Bool -> Bool
&& (e -> AVL e -> e -> Bool
isSortedLU e
e AVL e
r e
ul)
Ordering
_ -> Bool
False
Ordering
_ -> Bool
False
isSortedOK :: (e -> e -> Ordering) -> AVL e -> Bool
isSortedOK :: forall e. (e -> e -> Ordering) -> AVL e -> Bool
isSortedOK e -> e -> Ordering
c AVL e
t = (AVL e -> Bool
forall e. AVL e -> Bool
isBalanced AVL e
t) Bool -> Bool -> Bool
&& ((e -> e -> Ordering) -> AVL e -> Bool
forall e. (e -> e -> Ordering) -> AVL e -> Bool
isSorted e -> e -> Ordering
c AVL e
t)
minElements :: Int -> Integer
minElements :: Int -> Integer
minElements Int
0 = Integer
0
minElements Int
1 = Integer
1
minElements Int
h = Integer -> Integer -> Int -> Integer
forall {t} {t}. (Eq t, Num t, Num t) => t -> t -> t -> t
minElements' Integer
0 Integer
1 Int
h where
minElements' :: t -> t -> t -> t
minElements' t
n1 t
n2 t
2 = t
1 t -> t -> t
forall a. Num a => a -> a -> a
+ t
n1 t -> t -> t
forall a. Num a => a -> a -> a
+ t
n2
minElements' t
n1 t
n2 t
m = t -> t -> t -> t
minElements' t
n2 (t
1 t -> t -> t
forall a. Num a => a -> a -> a
+ t
n1 t -> t -> t
forall a. Num a => a -> a -> a
+ t
n2) (t
mt -> t -> t
forall a. Num a => a -> a -> a
-t
1)
maxElements :: Int -> Integer
maxElements :: Int -> Integer
maxElements Int
0 = Integer
0
maxElements Int
h = Integer -> Int -> Integer
forall {t} {t}. (Eq t, Num t, Num t) => t -> t -> t
maxElements' Integer
0 Int
h where
maxElements' :: t -> t -> t
maxElements' t
n1 t
1 = t
1 t -> t -> t
forall a. Num a => a -> a -> a
+ t
2t -> t -> t
forall a. Num a => a -> a -> a
*t
n1
maxElements' t
n1 t
m = t -> t -> t
maxElements' (t
1 t -> t -> t
forall a. Num a => a -> a -> a
+ t
2t -> t -> t
forall a. Num a => a -> a -> a
*t
n1) (t
mt -> t -> t
forall a. Num a => a -> a -> a
-t
1)