Homework-New/Hasklet1.hs

144 lines
3.4 KiB
Haskell

module Hasklet1 where
-- | A generic binary tree with values at internal nodes.
data Tree a = Node a (Tree a) (Tree a)
| Leaf
deriving (Eq,Show)
-- | Build a balanced binary tree from a list of values.
tree :: [a] -> Tree a
tree [] = Leaf
tree (x:xs) = Node x (tree l) (tree r)
where (l,r) = splitAt (length xs `div` 2) xs
-- Some example trees containing integers.
t1, t2, t3, t4 :: Tree Int
t1 = Node 1 Leaf (Node 2 Leaf Leaf)
t2 = Node 3 (Node 4 Leaf Leaf) Leaf
t3 = Node 5 t1 t2
t4 = tree (filter odd [1..100])
treeFold :: (a -> b -> b -> b) -> b -> Tree a -> b
treeFold _ b Leaf = b
treeFold f b (Node a t1 t2) = f a (treeFold f b t1) (treeFold f b t2)
-- An example tree containing a secret message!
t5 :: Tree Char
t5 = tree " bstyoouu rd oerrvialentikne"
-- | Define a recursive function that sums the numbers in a tree.
--
-- >>> sumTree Leaf
-- 0
--
-- >>> sumTree t3
-- 15
--
-- >>> sumTree t4
-- 2500
--
sumTree :: Num a => Tree a -> a
sumTree Leaf = 0
sumTree (Node a t1 t2) = a + sumTree t1 + sumTree t2
-- | Define a recursive function that checks whether a given element is
-- contained in a tree.
--
-- >>> contains 57 t4
-- True
--
-- >>> contains 58 t4
-- False
--
-- >>> contains 'k' t5
-- True
--
-- >>> contains 'z' t5
-- False
--
contains :: Eq a => a -> Tree a -> Bool
contains _ Leaf = False
contains v (Node a t1 t2) = v == a || contains v t1 || contains v t2
-- | Define a function for converting a binary tree of type 'Tree a' into
-- a value of type 'b' by folding an accumulator function over the tree.
-- You should start by writing a type definition for the function.
--
-- Note there is more than one correct type for this function! Part of your
-- task is to figure out the type. For inspiration, think about the types of
-- the functions `foldl` and `foldr` for lists.
--
foldTree :: (a -> b -> b -> b) -> b -> Tree a -> b
foldTree _ b Leaf = b
foldTree f b (Node a t1 t2) = f a (foldTree f b t1) (foldTree f b t2)
-- | Use 'foldTree' to define a new version of 'sumTree'.
--
-- >>> sumTreeFold Leaf
-- 0
--
-- >>> sumTreeFold t3
-- 15
--
-- >>> sumTreeFold t4
-- 2500
--
sumTreeFold :: Num a => Tree a -> a
sumTreeFold = foldTree ((.(+)).(.).(+)) 0
-- | Use 'foldTree' to define a new version of 'contains'.
--
-- >>> containsFold 57 t4
-- True
--
-- >>> containsFold 58 t4
-- False
--
-- >>> containsFold 'v' t5
-- True
--
-- >>> containsFold 'q' t5
-- False
--
containsFold :: Eq a => a -> Tree a -> Bool
containsFold v = foldTree (\a b c -> a == v || b || c) False
-- | Implement a function that returns a list of values contained at each
-- level of the tree. That is, it should return a nested list where the
-- first list contains the value at the root, the second list contains the
-- values at its children, the third list contains the values at the next
-- level down the tree, and so on.
--
-- Apply this function to 't5' to reveal the secret message!
--
-- >>> levels Leaf
-- []
--
-- >>> levels t1
-- [[1],[2]]
--
-- >>> levels t2
-- [[3],[4]]
--
-- >>> levels t3
-- [[5],[1,3],[2,4]]
--
-- >>> levels (tree [1..10])
-- [[1],[2,6],[3,4,7,9],[5,8,10]]
--
levels :: Tree a -> [[a]]
levels = foldTree (\a b c -> [a] : padded b c) []
where
padded [] xs = xs
padded xs [] = xs
padded (x:xs) (y:ys) = (x ++ y) : padded xs ys