[Haskell-cafe] Branches of a binary tree

Kyle L Bittinger kyle2 at MIT.EDU
Fri Jul 6 11:47:58 EDT 2007


I am writing some code to find peaks in molecular spectra. I represent a 
spectrum as a list of numbers (intensities) and build a binary search tree 
of the positions in the list (x-values) sorted by intensity.

Peaks in the spectrum appear as branches of the tree. My task is to return 
branches of a binary tree that contain no other branches larger than some 
size.

I wrote this function to test whether a tree can be classified as a peak. 
I suspect it's very inefficient, and it doesn't seem idiomatic to me 
either. I'm looking for suggestions to improve it:

-- |Returns True if the tree can be classified as a peak. Peaks are 
-- qualified by not having any two branches with a size greater than n.
isPeak :: Int -> Tree a -> Bool
isPeak _ Tip = True
isPeak n (Node _ l r)
   | (ltn l) && (ltn r) = True
   | (ltn l) && (gtn r) = isPeak n r
   | (gtn l) && (ltn r) = isPeak n l
   | (gtn l) && (gtn r) = False
   | otherwise          = error "isPeak: no matching condition in guard"
     where gtn = (>=n) . size
           ltn = (<n)  . size

The "things to avoid" section of the haskell wiki suggests using an 
"atLeast" function for testing the length of lists. I don't know how to 
write this for trees, but I could do something like:

           gtn = atLeast n . flatten
           ltn = not . gtn

The rest of my module is below. Most of it is standard binary tree stuff. 
Any suggestions would be much appreciated!

--Kyle

data Tree a = Tip | Node a (Tree a) (Tree a) deriving Show

insert :: Ord a => Tree a -> a -> Tree a
insert Tip x = Node x Tip Tip
insert (Node y l r) x | x <= y    = Node y (insert l x) r
                       | otherwise = Node y l (insert r x)

growTree :: Ord a => [a] -> Tree a
growTree = foldl insert Tip

size :: Tree a -> Int
size Tip = 0
size (Node x l r) = 1 + (size l) + (size r)

flatten :: Tree a -> [a]
flatten Tip = []
flatten (Node x l r) = flatten l ++ [x] ++ flatten r

atLeast :: Int -> [a] -> Bool
atLeast 0 _      = True
atLeast _ []     = False
atLeast n (_:ys) = atLeast (n-1) ys

peaks :: Int -> Tree a -> [[a]]
peaks _ Tip = []
peaks n t@(Node _ l r)
   | isPeak n t = [flatten t]
   | otherwise  = peaks n l ++ peaks n r

-- Stolen from <http://haskell.org/haskellwiki/Blow_your_mind>
sortIndicies ys = map fst $ L.sortBy (comparing snd) $ zip [0..] ys
   where comparing f x y = compare (f x) (f y)


More information about the Haskell-Cafe mailing list