{-# LANGUAGE DeriveFunctor #-}
module Tree234(treeFromList,
treeList, treeSearch, treeAdd, initTree234, Tree234) where
data Tree234 a = Leaf |
Leaf2 a |
Leaf3 a a |
Leaf4 a a a |
Node2 a (Tree234 a) (Tree234 a) |
Node3 a a (Tree234 a) (Tree234 a) (Tree234 a) |
Node4 a a a (Tree234 a) (Tree234 a) (Tree234 a) (Tree234 a)
deriving (Tree234 a -> Tree234 a -> Bool
forall a. Eq a => Tree234 a -> Tree234 a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Tree234 a -> Tree234 a -> Bool
$c/= :: forall a. Eq a => Tree234 a -> Tree234 a -> Bool
== :: Tree234 a -> Tree234 a -> Bool
$c== :: forall a. Eq a => Tree234 a -> Tree234 a -> Bool
Eq, Tree234 a -> Tree234 a -> Ordering
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall {a}. Ord a => Eq (Tree234 a)
forall a. Ord a => Tree234 a -> Tree234 a -> Bool
forall a. Ord a => Tree234 a -> Tree234 a -> Ordering
forall a. Ord a => Tree234 a -> Tree234 a -> Tree234 a
min :: Tree234 a -> Tree234 a -> Tree234 a
$cmin :: forall a. Ord a => Tree234 a -> Tree234 a -> Tree234 a
max :: Tree234 a -> Tree234 a -> Tree234 a
$cmax :: forall a. Ord a => Tree234 a -> Tree234 a -> Tree234 a
>= :: Tree234 a -> Tree234 a -> Bool
$c>= :: forall a. Ord a => Tree234 a -> Tree234 a -> Bool
> :: Tree234 a -> Tree234 a -> Bool
$c> :: forall a. Ord a => Tree234 a -> Tree234 a -> Bool
<= :: Tree234 a -> Tree234 a -> Bool
$c<= :: forall a. Ord a => Tree234 a -> Tree234 a -> Bool
< :: Tree234 a -> Tree234 a -> Bool
$c< :: forall a. Ord a => Tree234 a -> Tree234 a -> Bool
compare :: Tree234 a -> Tree234 a -> Ordering
$ccompare :: forall a. Ord a => Tree234 a -> Tree234 a -> Ordering
Ord,Int -> Tree234 a -> ShowS
forall a. Show a => Int -> Tree234 a -> ShowS
forall a. Show a => [Tree234 a] -> ShowS
forall a. Show a => Tree234 a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Tree234 a] -> ShowS
$cshowList :: forall a. Show a => [Tree234 a] -> ShowS
show :: Tree234 a -> String
$cshow :: forall a. Show a => Tree234 a -> String
showsPrec :: Int -> Tree234 a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> Tree234 a -> ShowS
Show, forall a b. a -> Tree234 b -> Tree234 a
forall a b. (a -> b) -> Tree234 a -> Tree234 b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: forall a b. a -> Tree234 b -> Tree234 a
$c<$ :: forall a b. a -> Tree234 b -> Tree234 a
fmap :: forall a b. (a -> b) -> Tree234 a -> Tree234 b
$cfmap :: forall a b. (a -> b) -> Tree234 a -> Tree234 b
Functor)
initTree234 :: Tree234 a
initTree234 = forall a. Tree234 a
Leaf
treeAdd :: (a -> a -> a)
-> (a -> a -> Tree234 a -> Tree234 a -> Tree234 a -> Tree234 a)
-> a
-> Tree234 a
-> Tree234 a
treeAdd a -> a -> a
comb a -> a -> Tree234 a -> Tree234 a -> Tree234 a -> Tree234 a
cmp a
a Tree234 a
t = forall {a}.
(a -> a -> a)
-> (a -> a -> Tree234 a -> Tree234 a -> Tree234 a -> Tree234 a)
-> a
-> (Tree234 a -> Tree234 a)
-> (a -> Tree234 a -> Tree234 a -> Tree234 a)
-> Tree234 a
-> Tree234 a
treeAdd' a -> a -> a
comb a -> a -> Tree234 a -> Tree234 a -> Tree234 a -> Tree234 a
cmp a
a forall a. a -> a
id forall a. a -> Tree234 a -> Tree234 a -> Tree234 a
Node2 Tree234 a
t
treeSearch :: t -> (t -> t) -> (t -> t -> t -> t -> t) -> Tree234 t -> t
treeSearch t
fail t -> t
cont t -> t -> t -> t -> t
p Tree234 t
Leaf = t
fail
treeSearch t
fail t -> t
cont t -> t -> t -> t -> t
p (Leaf2 t
a1) = t -> t -> t -> t -> t
p t
a1 t
fail (t -> t
cont t
a1) t
fail
treeSearch t
fail t -> t
cont t -> t -> t -> t -> t
p (Leaf3 t
a1 t
a2) =
t -> t -> t -> t -> t
p t
a1 t
fail (t -> t
cont t
a1) (t -> t -> t -> t -> t
p t
a2 t
fail (t -> t
cont t
a2) t
fail)
treeSearch t
fail t -> t
cont t -> t -> t -> t -> t
p (Leaf4 t
a1 t
a2 t
a3) =
t -> t -> t -> t -> t
p t
a2 (t -> t -> t -> t -> t
p t
a1 t
fail (t -> t
cont t
a1) t
fail) (t -> t
cont t
a2) (t -> t -> t -> t -> t
p t
a3 t
fail (t -> t
cont t
a3) t
fail)
treeSearch t
fail t -> t
cont t -> t -> t -> t -> t
p (Node2 t
a1 Tree234 t
t1 Tree234 t
t2) =
t -> t -> t -> t -> t
p t
a1 (t -> (t -> t) -> (t -> t -> t -> t -> t) -> Tree234 t -> t
treeSearch t
fail t -> t
cont t -> t -> t -> t -> t
p Tree234 t
t1) (t -> t
cont t
a1) (t -> (t -> t) -> (t -> t -> t -> t -> t) -> Tree234 t -> t
treeSearch t
fail t -> t
cont t -> t -> t -> t -> t
p Tree234 t
t2)
treeSearch t
fail t -> t
cont t -> t -> t -> t -> t
p (Node3 t
a1 t
a2 Tree234 t
t1 Tree234 t
t2 Tree234 t
t3) =
t -> t -> t -> t -> t
p t
a1
(t -> (t -> t) -> (t -> t -> t -> t -> t) -> Tree234 t -> t
treeSearch t
fail t -> t
cont t -> t -> t -> t -> t
p Tree234 t
t1)
(t -> t
cont t
a1)
(t -> t -> t -> t -> t
p t
a2
(t -> (t -> t) -> (t -> t -> t -> t -> t) -> Tree234 t -> t
treeSearch t
fail t -> t
cont t -> t -> t -> t -> t
p Tree234 t
t2)
(t -> t
cont t
a2)
(t -> (t -> t) -> (t -> t -> t -> t -> t) -> Tree234 t -> t
treeSearch t
fail t -> t
cont t -> t -> t -> t -> t
p Tree234 t
t3))
treeSearch t
fail t -> t
cont t -> t -> t -> t -> t
p (Node4 t
a1 t
a2 t
a3 Tree234 t
t1 Tree234 t
t2 Tree234 t
t3 Tree234 t
t4) =
t -> t -> t -> t -> t
p t
a2
(t -> t -> t -> t -> t
p t
a1
(t -> (t -> t) -> (t -> t -> t -> t -> t) -> Tree234 t -> t
treeSearch t
fail t -> t
cont t -> t -> t -> t -> t
p Tree234 t
t1)
(t -> t
cont t
a1)
(t -> (t -> t) -> (t -> t -> t -> t -> t) -> Tree234 t -> t
treeSearch t
fail t -> t
cont t -> t -> t -> t -> t
p Tree234 t
t2))
(t -> t
cont t
a2)
(t -> t -> t -> t -> t
p t
a3
(t -> (t -> t) -> (t -> t -> t -> t -> t) -> Tree234 t -> t
treeSearch t
fail t -> t
cont t -> t -> t -> t -> t
p Tree234 t
t3)
(t -> t
cont t
a3)
(t -> (t -> t) -> (t -> t -> t -> t -> t) -> Tree234 t -> t
treeSearch t
fail t -> t
cont t -> t -> t -> t -> t
p Tree234 t
t4))
treeMapList :: (t -> [a]) -> Tree234 t -> [a]
treeMapList t -> [a]
f Tree234 t
Leaf = []
treeMapList t -> [a]
f (Leaf2 t
a1) = t -> [a]
f t
a1
treeMapList t -> [a]
f (Leaf3 t
a1 t
a2) = t -> [a]
f t
a1 forall a. [a] -> [a] -> [a]
++ t -> [a]
f t
a2
treeMapList t -> [a]
f (Leaf4 t
a1 t
a2 t
a3) = t -> [a]
f t
a1 forall a. [a] -> [a] -> [a]
++ t -> [a]
f t
a2 forall a. [a] -> [a] -> [a]
++ t -> [a]
f t
a3
treeMapList t -> [a]
f (Node2 t
a1 Tree234 t
t1 Tree234 t
t2) =
(t -> [a]) -> Tree234 t -> [a]
treeMapList t -> [a]
f Tree234 t
t1 forall a. [a] -> [a] -> [a]
++ t -> [a]
f t
a1 forall a. [a] -> [a] -> [a]
++ (t -> [a]) -> Tree234 t -> [a]
treeMapList t -> [a]
f Tree234 t
t2
treeMapList t -> [a]
f (Node3 t
a1 t
a2 Tree234 t
t1 Tree234 t
t2 Tree234 t
t3) =
(t -> [a]) -> Tree234 t -> [a]
treeMapList t -> [a]
f Tree234 t
t1 forall a. [a] -> [a] -> [a]
++
t -> [a]
f t
a1 forall a. [a] -> [a] -> [a]
++ (t -> [a]) -> Tree234 t -> [a]
treeMapList t -> [a]
f Tree234 t
t2 forall a. [a] -> [a] -> [a]
++ t -> [a]
f t
a2 forall a. [a] -> [a] -> [a]
++ (t -> [a]) -> Tree234 t -> [a]
treeMapList t -> [a]
f Tree234 t
t3
treeMapList t -> [a]
f (Node4 t
a1 t
a2 t
a3 Tree234 t
t1 Tree234 t
t2 Tree234 t
t3 Tree234 t
t4) =
(t -> [a]) -> Tree234 t -> [a]
treeMapList t -> [a]
f Tree234 t
t1 forall a. [a] -> [a] -> [a]
++
t -> [a]
f t
a1 forall a. [a] -> [a] -> [a]
++
(t -> [a]) -> Tree234 t -> [a]
treeMapList t -> [a]
f Tree234 t
t2 forall a. [a] -> [a] -> [a]
++
t -> [a]
f t
a2 forall a. [a] -> [a] -> [a]
++ (t -> [a]) -> Tree234 t -> [a]
treeMapList t -> [a]
f Tree234 t
t3 forall a. [a] -> [a] -> [a]
++ t -> [a]
f t
a3 forall a. [a] -> [a] -> [a]
++ (t -> [a]) -> Tree234 t -> [a]
treeMapList t -> [a]
f Tree234 t
t4
treeFromList :: (a -> a -> a)
-> (a -> a -> Tree234 a -> Tree234 a -> Tree234 a -> Tree234 a)
-> [a]
-> Tree234 a
treeFromList a -> a -> a
comb a -> a -> Tree234 a -> Tree234 a -> Tree234 a -> Tree234 a
cmp [a]
l = forall {a}.
(a -> a -> a)
-> (a -> a -> Tree234 a -> Tree234 a -> Tree234 a -> Tree234 a)
-> [a]
-> Tree234 a
-> Tree234 a
treeAddList a -> a -> a
comb a -> a -> Tree234 a -> Tree234 a -> Tree234 a -> Tree234 a
cmp [a]
l forall a. Tree234 a
Leaf
treeAddList :: (a -> a -> a)
-> (a -> a -> Tree234 a -> Tree234 a -> Tree234 a -> Tree234 a)
-> [a]
-> Tree234 a
-> Tree234 a
treeAddList a -> a -> a
comb a -> a -> Tree234 a -> Tree234 a -> Tree234 a -> Tree234 a
cmp [] Tree234 a
t = Tree234 a
t
treeAddList a -> a -> a
comb a -> a -> Tree234 a -> Tree234 a -> Tree234 a -> Tree234 a
cmp (a
x : [a]
xs) Tree234 a
t =
(a -> a -> a)
-> (a -> a -> Tree234 a -> Tree234 a -> Tree234 a -> Tree234 a)
-> [a]
-> Tree234 a
-> Tree234 a
treeAddList a -> a -> a
comb a -> a -> Tree234 a -> Tree234 a -> Tree234 a -> Tree234 a
cmp [a]
xs (forall {a}.
(a -> a -> a)
-> (a -> a -> Tree234 a -> Tree234 a -> Tree234 a -> Tree234 a)
-> a
-> Tree234 a
-> Tree234 a
treeAdd a -> a -> a
comb a -> a -> Tree234 a -> Tree234 a -> Tree234 a -> Tree234 a
cmp a
x Tree234 a
t)
treeAdd' :: (a -> a -> a)
-> (a -> a -> Tree234 a -> Tree234 a -> Tree234 a -> Tree234 a)
-> a
-> (Tree234 a -> Tree234 a)
-> (a -> Tree234 a -> Tree234 a -> Tree234 a)
-> Tree234 a
-> Tree234 a
treeAdd' a -> a -> a
comb a -> a -> Tree234 a -> Tree234 a -> Tree234 a -> Tree234 a
cmp a
a Tree234 a -> Tree234 a
keep a -> Tree234 a -> Tree234 a -> Tree234 a
split Tree234 a
Leaf = Tree234 a -> Tree234 a
keep (forall a. a -> Tree234 a
Leaf2 a
a)
treeAdd' a -> a -> a
comb a -> a -> Tree234 a -> Tree234 a -> Tree234 a -> Tree234 a
cmp a
a Tree234 a -> Tree234 a
keep a -> Tree234 a -> Tree234 a -> Tree234 a
split (Leaf2 a
a1) =
Tree234 a -> Tree234 a
keep (a -> a -> Tree234 a -> Tree234 a -> Tree234 a -> Tree234 a
cmp a
a a
a1 (forall a. a -> a -> Tree234 a
Leaf3 a
a a
a1) (forall a. a -> Tree234 a
Leaf2 (a -> a -> a
comb a
a a
a1)) (forall a. a -> a -> Tree234 a
Leaf3 a
a1 a
a))
treeAdd' a -> a -> a
comb a -> a -> Tree234 a -> Tree234 a -> Tree234 a -> Tree234 a
cmp a
a Tree234 a -> Tree234 a
keep a -> Tree234 a -> Tree234 a -> Tree234 a
split (Leaf3 a
a1 a
a2) =
Tree234 a -> Tree234 a
keep (a -> a -> Tree234 a -> Tree234 a -> Tree234 a -> Tree234 a
cmp a
a
a
a1
(forall a. a -> a -> a -> Tree234 a
Leaf4 a
a a
a1 a
a2)
(forall a. a -> a -> Tree234 a
Leaf3 (a -> a -> a
comb a
a a
a1) a
a2)
(a -> a -> Tree234 a -> Tree234 a -> Tree234 a -> Tree234 a
cmp a
a a
a2 (forall a. a -> a -> a -> Tree234 a
Leaf4 a
a1 a
a a
a2) (forall a. a -> a -> Tree234 a
Leaf3 a
a1 (a -> a -> a
comb a
a a
a2)) (forall a. a -> a -> a -> Tree234 a
Leaf4 a
a1 a
a2 a
a)))
treeAdd' a -> a -> a
comb a -> a -> Tree234 a -> Tree234 a -> Tree234 a -> Tree234 a
cmp a
a Tree234 a -> Tree234 a
keep a -> Tree234 a -> Tree234 a -> Tree234 a
split (Leaf4 a
a1 a
a2 a
a3) =
a -> a -> Tree234 a -> Tree234 a -> Tree234 a -> Tree234 a
cmp a
a
a
a2
(a -> a -> Tree234 a -> Tree234 a -> Tree234 a -> Tree234 a
cmp a
a
a
a1
(a -> Tree234 a -> Tree234 a -> Tree234 a
split a
a2 (forall a. a -> a -> Tree234 a
Leaf3 a
a a
a1) (forall a. a -> Tree234 a
Leaf2 a
a3))
(Tree234 a -> Tree234 a
keep (forall a. a -> a -> a -> Tree234 a
Leaf4 (a -> a -> a
comb a
a a
a1) a
a2 a
a3))
(a -> Tree234 a -> Tree234 a -> Tree234 a
split a
a2 (forall a. a -> a -> Tree234 a
Leaf3 a
a1 a
a) (forall a. a -> Tree234 a
Leaf2 a
a3)))
(Tree234 a -> Tree234 a
keep (forall a. a -> a -> a -> Tree234 a
Leaf4 a
a1 (a -> a -> a
comb a
a a
a2) a
a3))
(a -> a -> Tree234 a -> Tree234 a -> Tree234 a -> Tree234 a
cmp a
a
a
a3
(a -> Tree234 a -> Tree234 a -> Tree234 a
split a
a2 (forall a. a -> Tree234 a
Leaf2 a
a1) (forall a. a -> a -> Tree234 a
Leaf3 a
a a
a3))
(Tree234 a -> Tree234 a
keep (forall a. a -> a -> a -> Tree234 a
Leaf4 a
a1 a
a2 (a -> a -> a
comb a
a a
a3)))
(a -> Tree234 a -> Tree234 a -> Tree234 a
split a
a2 (forall a. a -> Tree234 a
Leaf2 a
a1) (forall a. a -> a -> Tree234 a
Leaf3 a
a3 a
a)))
treeAdd' a -> a -> a
comb a -> a -> Tree234 a -> Tree234 a -> Tree234 a -> Tree234 a
cmp a
a Tree234 a -> Tree234 a
keep a -> Tree234 a -> Tree234 a -> Tree234 a
split (Node2 a
a1 Tree234 a
t1 Tree234 a
t2) =
Tree234 a -> Tree234 a
keep (a -> a -> Tree234 a -> Tree234 a -> Tree234 a -> Tree234 a
cmp a
a
a
a1
((a -> a -> a)
-> (a -> a -> Tree234 a -> Tree234 a -> Tree234 a -> Tree234 a)
-> a
-> (Tree234 a -> Tree234 a)
-> (a -> Tree234 a -> Tree234 a -> Tree234 a)
-> Tree234 a
-> Tree234 a
treeAdd' a -> a -> a
comb
a -> a -> Tree234 a -> Tree234 a -> Tree234 a -> Tree234 a
cmp
a
a
(\Tree234 a
t1' -> forall a. a -> Tree234 a -> Tree234 a -> Tree234 a
Node2 a
a1 Tree234 a
t1' Tree234 a
t2)
(\a
a0' -> \Tree234 a
t0' -> \Tree234 a
t1' -> forall a.
a -> a -> Tree234 a -> Tree234 a -> Tree234 a -> Tree234 a
Node3 a
a0' a
a1 Tree234 a
t0' Tree234 a
t1' Tree234 a
t2)
Tree234 a
t1)
(forall a. a -> Tree234 a -> Tree234 a -> Tree234 a
Node2 (a -> a -> a
comb a
a a
a1) Tree234 a
t1 Tree234 a
t2)
((a -> a -> a)
-> (a -> a -> Tree234 a -> Tree234 a -> Tree234 a -> Tree234 a)
-> a
-> (Tree234 a -> Tree234 a)
-> (a -> Tree234 a -> Tree234 a -> Tree234 a)
-> Tree234 a
-> Tree234 a
treeAdd' a -> a -> a
comb
a -> a -> Tree234 a -> Tree234 a -> Tree234 a -> Tree234 a
cmp
a
a
(\Tree234 a
t2' -> forall a. a -> Tree234 a -> Tree234 a -> Tree234 a
Node2 a
a1 Tree234 a
t1 Tree234 a
t2')
(\a
a2' -> \Tree234 a
t2' -> \Tree234 a
t3' -> forall a.
a -> a -> Tree234 a -> Tree234 a -> Tree234 a -> Tree234 a
Node3 a
a1 a
a2' Tree234 a
t1 Tree234 a
t2' Tree234 a
t3')
Tree234 a
t2))
treeAdd' a -> a -> a
comb a -> a -> Tree234 a -> Tree234 a -> Tree234 a -> Tree234 a
cmp a
a Tree234 a -> Tree234 a
keep a -> Tree234 a -> Tree234 a -> Tree234 a
split (Node3 a
a1 a
a2 Tree234 a
t1 Tree234 a
t2 Tree234 a
t3) =
Tree234 a -> Tree234 a
keep (a -> a -> Tree234 a -> Tree234 a -> Tree234 a -> Tree234 a
cmp a
a
a
a1
((a -> a -> a)
-> (a -> a -> Tree234 a -> Tree234 a -> Tree234 a -> Tree234 a)
-> a
-> (Tree234 a -> Tree234 a)
-> (a -> Tree234 a -> Tree234 a -> Tree234 a)
-> Tree234 a
-> Tree234 a
treeAdd' a -> a -> a
comb
a -> a -> Tree234 a -> Tree234 a -> Tree234 a -> Tree234 a
cmp
a
a
(\Tree234 a
t1' -> forall a.
a -> a -> Tree234 a -> Tree234 a -> Tree234 a -> Tree234 a
Node3 a
a1 a
a2 Tree234 a
t1' Tree234 a
t2 Tree234 a
t3)
(\a
a0' -> \Tree234 a
t0' -> \Tree234 a
t1' -> forall a.
a
-> a
-> a
-> Tree234 a
-> Tree234 a
-> Tree234 a
-> Tree234 a
-> Tree234 a
Node4 a
a0' a
a1 a
a2 Tree234 a
t0' Tree234 a
t1' Tree234 a
t2 Tree234 a
t3)
Tree234 a
t1)
(forall a.
a -> a -> Tree234 a -> Tree234 a -> Tree234 a -> Tree234 a
Node3 (a -> a -> a
comb a
a a
a1) a
a2 Tree234 a
t1 Tree234 a
t2 Tree234 a
t3)
(a -> a -> Tree234 a -> Tree234 a -> Tree234 a -> Tree234 a
cmp a
a
a
a2
((a -> a -> a)
-> (a -> a -> Tree234 a -> Tree234 a -> Tree234 a -> Tree234 a)
-> a
-> (Tree234 a -> Tree234 a)
-> (a -> Tree234 a -> Tree234 a -> Tree234 a)
-> Tree234 a
-> Tree234 a
treeAdd' a -> a -> a
comb
a -> a -> Tree234 a -> Tree234 a -> Tree234 a -> Tree234 a
cmp
a
a
(\Tree234 a
t2' -> forall a.
a -> a -> Tree234 a -> Tree234 a -> Tree234 a -> Tree234 a
Node3 a
a1 a
a2 Tree234 a
t1 Tree234 a
t2' Tree234 a
t3)
(\a
a1_5' ->
\Tree234 a
t1_5' ->
\Tree234 a
t2' -> forall a.
a
-> a
-> a
-> Tree234 a
-> Tree234 a
-> Tree234 a
-> Tree234 a
-> Tree234 a
Node4 a
a1 a
a1_5' a
a2 Tree234 a
t1 Tree234 a
t1_5' Tree234 a
t2' Tree234 a
t3)
Tree234 a
t2)
(forall a.
a -> a -> Tree234 a -> Tree234 a -> Tree234 a -> Tree234 a
Node3 a
a1 (a -> a -> a
comb a
a a
a2) Tree234 a
t1 Tree234 a
t2 Tree234 a
t3)
((a -> a -> a)
-> (a -> a -> Tree234 a -> Tree234 a -> Tree234 a -> Tree234 a)
-> a
-> (Tree234 a -> Tree234 a)
-> (a -> Tree234 a -> Tree234 a -> Tree234 a)
-> Tree234 a
-> Tree234 a
treeAdd' a -> a -> a
comb
a -> a -> Tree234 a -> Tree234 a -> Tree234 a -> Tree234 a
cmp
a
a
(\Tree234 a
t3' -> forall a.
a -> a -> Tree234 a -> Tree234 a -> Tree234 a -> Tree234 a
Node3 a
a1 a
a2 Tree234 a
t1 Tree234 a
t2 Tree234 a
t3')
(\a
a3' ->
\Tree234 a
t3' -> \Tree234 a
t4' -> forall a.
a
-> a
-> a
-> Tree234 a
-> Tree234 a
-> Tree234 a
-> Tree234 a
-> Tree234 a
Node4 a
a1 a
a2 a
a3' Tree234 a
t1 Tree234 a
t2 Tree234 a
t3' Tree234 a
t4')
Tree234 a
t3)))
treeAdd' a -> a -> a
comb a -> a -> Tree234 a -> Tree234 a -> Tree234 a -> Tree234 a
cmp a
a Tree234 a -> Tree234 a
keep a -> Tree234 a -> Tree234 a -> Tree234 a
split (Node4 a
a1 a
a2 a
a3 Tree234 a
t1 Tree234 a
t2 Tree234 a
t3 Tree234 a
t4) =
a -> a -> Tree234 a -> Tree234 a -> Tree234 a -> Tree234 a
cmp a
a
a
a2
(a -> a -> Tree234 a -> Tree234 a -> Tree234 a -> Tree234 a
cmp a
a
a
a1
(a -> Tree234 a -> Tree234 a -> Tree234 a
split a
a2
((a -> a -> a)
-> (a -> a -> Tree234 a -> Tree234 a -> Tree234 a -> Tree234 a)
-> a
-> (Tree234 a -> Tree234 a)
-> (a -> Tree234 a -> Tree234 a -> Tree234 a)
-> Tree234 a
-> Tree234 a
treeAdd' a -> a -> a
comb
a -> a -> Tree234 a -> Tree234 a -> Tree234 a -> Tree234 a
cmp
a
a
(\Tree234 a
t1' -> forall a. a -> Tree234 a -> Tree234 a -> Tree234 a
Node2 a
a1 Tree234 a
t1' Tree234 a
t2)
(\a
a0' -> \Tree234 a
t0' -> \Tree234 a
t1' -> forall a.
a -> a -> Tree234 a -> Tree234 a -> Tree234 a -> Tree234 a
Node3 a
a0' a
a1 Tree234 a
t0' Tree234 a
t1' Tree234 a
t2)
Tree234 a
t1)
(forall a. a -> Tree234 a -> Tree234 a -> Tree234 a
Node2 a
a3 Tree234 a
t3 Tree234 a
t4))
(Tree234 a -> Tree234 a
keep (forall a.
a
-> a
-> a
-> Tree234 a
-> Tree234 a
-> Tree234 a
-> Tree234 a
-> Tree234 a
Node4 (a -> a -> a
comb a
a a
a1) a
a2 a
a3 Tree234 a
t1 Tree234 a
t2 Tree234 a
t3 Tree234 a
t4))
(a -> Tree234 a -> Tree234 a -> Tree234 a
split a
a2
((a -> a -> a)
-> (a -> a -> Tree234 a -> Tree234 a -> Tree234 a -> Tree234 a)
-> a
-> (Tree234 a -> Tree234 a)
-> (a -> Tree234 a -> Tree234 a -> Tree234 a)
-> Tree234 a
-> Tree234 a
treeAdd' a -> a -> a
comb
a -> a -> Tree234 a -> Tree234 a -> Tree234 a -> Tree234 a
cmp
a
a
(\Tree234 a
t2' -> forall a. a -> Tree234 a -> Tree234 a -> Tree234 a
Node2 a
a1 Tree234 a
t1 Tree234 a
t2')
(\a
a2' -> \Tree234 a
t2' -> \Tree234 a
t3' -> forall a.
a -> a -> Tree234 a -> Tree234 a -> Tree234 a -> Tree234 a
Node3 a
a1 a
a2' Tree234 a
t1 Tree234 a
t2' Tree234 a
t3')
Tree234 a
t2)
(forall a. a -> Tree234 a -> Tree234 a -> Tree234 a
Node2 a
a3 Tree234 a
t3 Tree234 a
t4)))
(Tree234 a -> Tree234 a
keep (forall a.
a
-> a
-> a
-> Tree234 a
-> Tree234 a
-> Tree234 a
-> Tree234 a
-> Tree234 a
Node4 a
a1 (a -> a -> a
comb a
a a
a2) a
a3 Tree234 a
t1 Tree234 a
t2 Tree234 a
t3 Tree234 a
t4))
(a -> a -> Tree234 a -> Tree234 a -> Tree234 a -> Tree234 a
cmp a
a
a
a3
(a -> Tree234 a -> Tree234 a -> Tree234 a
split a
a2
(forall a. a -> Tree234 a -> Tree234 a -> Tree234 a
Node2 a
a1 Tree234 a
t1 Tree234 a
t2)
((a -> a -> a)
-> (a -> a -> Tree234 a -> Tree234 a -> Tree234 a -> Tree234 a)
-> a
-> (Tree234 a -> Tree234 a)
-> (a -> Tree234 a -> Tree234 a -> Tree234 a)
-> Tree234 a
-> Tree234 a
treeAdd' a -> a -> a
comb
a -> a -> Tree234 a -> Tree234 a -> Tree234 a -> Tree234 a
cmp
a
a
(\Tree234 a
t3' -> forall a. a -> Tree234 a -> Tree234 a -> Tree234 a
Node2 a
a3 Tree234 a
t3' Tree234 a
t4)
(\a
a2' -> \Tree234 a
t2' -> \Tree234 a
t3' -> forall a.
a -> a -> Tree234 a -> Tree234 a -> Tree234 a -> Tree234 a
Node3 a
a2' a
a3 Tree234 a
t2' Tree234 a
t3' Tree234 a
t4)
Tree234 a
t3))
(Tree234 a -> Tree234 a
keep (forall a.
a
-> a
-> a
-> Tree234 a
-> Tree234 a
-> Tree234 a
-> Tree234 a
-> Tree234 a
Node4 a
a1 a
a2 (a -> a -> a
comb a
a a
a3) Tree234 a
t1 Tree234 a
t2 Tree234 a
t3 Tree234 a
t4))
(a -> Tree234 a -> Tree234 a -> Tree234 a
split a
a2
(forall a. a -> Tree234 a -> Tree234 a -> Tree234 a
Node2 a
a1 Tree234 a
t1 Tree234 a
t2)
((a -> a -> a)
-> (a -> a -> Tree234 a -> Tree234 a -> Tree234 a -> Tree234 a)
-> a
-> (Tree234 a -> Tree234 a)
-> (a -> Tree234 a -> Tree234 a -> Tree234 a)
-> Tree234 a
-> Tree234 a
treeAdd' a -> a -> a
comb
a -> a -> Tree234 a -> Tree234 a -> Tree234 a -> Tree234 a
cmp
a
a
(\Tree234 a
t4' -> forall a. a -> Tree234 a -> Tree234 a -> Tree234 a
Node2 a
a3 Tree234 a
t3 Tree234 a
t4')
(\a
a4' -> \Tree234 a
t4' -> \Tree234 a
t5' -> forall a.
a -> a -> Tree234 a -> Tree234 a -> Tree234 a -> Tree234 a
Node3 a
a3 a
a4' Tree234 a
t3 Tree234 a
t4' Tree234 a
t5')
Tree234 a
t4)))
treeList :: Tree234 a -> [a]
treeList Tree234 a
t = forall {t} {a}. (t -> [a]) -> Tree234 t -> [a]
treeMapList (forall a. a -> [a] -> [a]
: []) Tree234 a
t