Finding max branching in a given tree in Haskell - haskell

I am a beginner in Haskell. Here I am trying to understand a Haskell function which calculates the max degree of branching in a Tree.
Here is the data type:
data Tree a = Node a [Tree a] deriving (Show)
leaf :: a -> Tree a
leaf a = Node a []
Here is the implementation:
maxBranching :: Tree a -> Int
maxBranching (Node _ ts) = let localBranching = length ts in
max localBranching (maxBranchingOfSubtrees ts)
where maxBranchingOfSubtrees :: [Tree a] -> Int
maxBranchingOfSubtrees [] = 0
maxBranchingOfSubtrees (x:xs) = max (maxBranching x) (maxBranchingOfSubtrees xs)
And here is the sample input:
Node 2 [leaf 7, Node 3 [leaf 0], Node 1 [leaf 3, leaf 2]]
I am not understanding this expression:
maxBranchingOfSubtrees (x:xs) = max (maxBranching x) (maxBranchingOfSubtrees xs)
How is max comparing the first element with the rest of the list, and where is it updating the max after each iteration? If I see when first element of the list as Leaf 7 would be passed as maxBranching x, there is no such case for that, how it returns the length of the first element of the list and then how is maxBranchingOfSubtress dealing with the rest of the list? Whereas, at first the localBranching contains the list length = 4? Any kind of detailed help would be appreciated.

Simple answer to your question is, all types fit together perfectly.
If (x:xs) :: [Tree a], then x :: Tree a and xs :: [Tree a], because (:) :: a -> [a] -> [a], or here specifically, (:) :: Tree a -> [Tree a] -> [Tree a]:
(:) :: Tree a -> [Tree a] -> [Tree a]
( x : xs ) :: [Tree a]
----------------------------------
x :: Tree a xs :: [Tree a]
And from the functions' signatures we have
maxBranching :: Tree a -> Int
x :: Tree a
---------------------------------
(maxBranching x) :: Int
and
maxBranchingOfSubtrees :: [Tree a] -> Int
xs :: [Tree a]
---------------------------------------------
(maxBranchingOfSubtrees xs) :: Int
so then we indeed can have
max :: Int -> Int -> Int
max (maxBranching x) (maxBranchingOfSubtrees xs) :: Int
So max is not "comparing the first element with the rest of the list". Instead, it compares the result of calculating maxBranching on the first element, with the result of calculating maxBranchingOfSubtrees on the rest of the list.
And that last bit, how does it know how to do that, you ask? By just using the same maxBranchingOfSubtrees recipe. In other words, by doing the same thing -- but this time with a "smaller" thing than before. A list's tail is a part of the list.
So eventually this recursion will run its course and we will have our answer -- if the list of trees is not infinite, that is. So this assumes that the branching factor isn't infinite.
So this finds the maximum branching factor of a node's sub-trees, then compares it with the branching factor of this node, to produce the maximum value overall.
Another view of it is that
maxBranchingOfSubtrees [] = 0
maxBranchingOfSubtrees (x:xs) = max (maxBranching x) (maxBranchingOfSubtrees xs)
= (max . maxBranching) x (maxBranchingOfSubtrees xs)
fits the foldr pattern,
maxBranchingOfSubtrees = foldr (max . maxBranching) 0
and this fits the mapping pattern,
maxBranchingOfSubtrees = foldr max 0 . map maxBranching
and there's a built-in function for that,
maxBranchingOfSubtrees = maximum . (0 :) . map maxBranching
and so substituting this into the main function we get
maxBranching :: Tree a -> Int
maxBranching (Node _ ts) = max (length ts) (maxBranchingOfSubtrees ts)
= max (length ts) (maximum (0 : map maxBranching ts))
= maximum (length ts : map maxBranching ts)
which uses higher order functions to express the same algorithm, instead of the hand-rolled recursion loop.

Related

How does repmin place values in the tree in Haskell?

I really like the repmin problem:
Write down repmin :: Tree Int -> Tree Int, which replaces all the numbers in the tree by their minimum in a single pass.
If I were writing something like this in python, I would go for passing values by their reference (let's say one-element lists instead of numbers is good enough):
def repmin(tree, wrapped_min_link=None):
x, subforest = tree
if wrapped_min_link is None:
wrapped_min_link = [x]
else:
[m] = wrapped_min_link
wrapped_min_link = [min(m, x)]
n = len(subforest)
subforest_min = [None] * n
for i in range(n):
if subforest[i]:
subforest_min[i] = repmin(subforest[i], wrapped_min_link)
return (wrapped_min_link, subforest_min)
It seems to me like a fitting way to wrap one's head around the knot-tying solution in Haskell (I wrote this one for rose trees from Data.Tree):
copyRose :: Tree Int -> Int -> (Tree Int, Int)
copyRose (Node x []) m = (Node m [], x)
copyRose (Node x fo) m =
let
unzipIdMinimum =
foldr (\ ~(a, b) ~(as, bmin) -> (a:as, b `min` bmin)) ([], maxBound :: Int)
(fo', y) = unzipIdMinimum . map (flip copyRose m) $ fo
in (Node m fo', x `min` y)
repmin :: Tree Int -> Tree Int
repmin = (loop . uncurry) copyRose
Yet, I reckon the solutions to work very differently. Here is my understanding of the latter one:
Let us rewrite loop for (->) a bit:
loop f b = let cd = f (b, snd cd) in fst cd
I reckon it to be loop for (->)'s workalike as snd gives the same degree of laziness as pattern-matching within let.
So, when repmin traverses through the tree, it is:
Building up the minimum in the tree to be returned as the second element of the pair.
Leaves snd $ copyRose (tree, m) behind in every node.
Thus, when the traversal comes to an end, the programme knows the value of snd $ copyRose (tree, m) (that is, the minimum in the tree) and is able to show it whenever some node of the tree is being computed.
Do I understand repmin in Haskell correctly?
This is more an extended comment than an answer, but I don't really think of your implementation as single-pass. It looks like it traverses the tree once, producing a new, lazily-generated, tree and the global minimum, but it actually produces a lazily generated tree and an enormous tree of thunks that will eventually calculate the minimum. To avoid this, you can get closer to the Python code by generating the tree eagerly, keeping track of the minimum as you go.
You'll note that I've generalized the type from Int to an arbitrary Ord type. You'll also note that I've used to different type variables to refer to the type of elements in the given tree and the type of the minimum passed in to generate a new tree—this lets the type system tell me if I mix them up.
repmin :: Tree a -> Tree a
repmin = (loop . uncurry) copyRose
copyRose :: Ord a => Tree a -> b -> (Tree b, a)
copyRose (Node x ts) final_min
| (ts', m) <- copyForest x ts final_min
= (Node final_min ts', m)
copyForest :: Ord a => a -> [Tree a] -> b -> ([Tree b], a)
copyForest !m [] _final_min = ([], m)
copyForest !m (t : ts) final_min
| (t', m') <- copyTree m t final_min
, (ts', m'') <- copyForest m' ts final_min
= (t' : ts', m'')
copyTree :: Ord a => a -> Tree a -> b -> (Tree b, a)
copyTree !m (Node x ts) final_min
| (ts', m') <- copyForest (min m x) ts final_min
= (Node final_min ts', m')
Exercise: rewrite this in monadic style using ReaderT to pass the global minimum and State to keep track of the minimum so far.

How to fix the errors about return subtrees from the depth given in parameter

I want to return the list of all the subtrees of the initial tree with the depth given in parameter
I've tried to return the list of the tree when the depth is 0 and when depth matching with n, I want to decrement n and apply the map function using my function and the n parameter decremented to the list of subtrees
data Tree t = Node t [Tree t] deriving (Show, Eq)
exTree :: Tree Int
exTree = Node 1 [ Node 2 [], Node 3 [ Node 4 [], Node 5 [],Node 6 []]]
height :: Tree t -> Int
height (Node _ []) = 1
height (Node _ l) = 1 + maximum (map height l)
treemap :: (t->t) -> Tree t -> Tree t
treemap f (Node x []) = Node (f x) []
treemap f (Node x l) = Node (f x) (map (treemap f) l)
-- Here is the function concerned:
extrForest :: Int -> Tree t -> [Tree t]
extrForest 0 a = [a]
extrForest n (Node _ l) = map (extrForest (n-1)) l
Here is the error message:
Couldn't match type ‘[Tree t]’ with ‘Tree t’
Expected type: Tree t -> Tree t
Actual type: Tree t -> [Tree t]
Relevant bindings include
l :: [Tree t] (bound at ds2.hs:16:22)
extrForest :: Int -> Tree t -> [Tree t] (bound at ds2.hs:15:1)
In the first argument of ‘map’, namely ‘(extrForest (n - 1))’
In the expression: map (extrForest (n - 1)) l
Still don't quite understand what you need, so here is a very ad-hoc solution.
Looking at your error, it is clear that you have the common problem [a] vs [[a]].
When you look at the type signature map :: (a -> b) -> [a] -> [b] you see that your function has to take an [a] and return a simple [b], not [[b]], as this then needs to be mapped over again. However, your extForest returns a list of forests, so what you should do, is to concatenate them: concat . map. Turns out this is a common thing, and there's a Prelude function to do this: concatMap :: Foldable t => (a -> [b]) -> t a -> [b].

Postorder traversal of binary tree with recursive data type

I'm trying to create a function for a post-order traversal of a recursive data type that creates an binary tree where the examples could create as many child leafs as possible. I've tried to set the nodes to left:root:right but the error doesn't recognize them - however, it would recognize (y:ys). It also recognizes root as an Int no matter if I use () or [] or nothing around it. What am I missing?
This is the data type and some easy examples to test it with:
data BiTree a = L a
| N [BiTree a]
ex1 :: BiTree Int
ex1 = N [(L 1),(L 1),(L 3)]
ex2 :: BiTree Int
ex2 = N [(L 1),(N[(L 2),(L 3)]),(L 4)]
Here's the code I wrote:
postord :: BiTree a -> [Int]
postord (L x) = [x]
postord (N (left:root:right)) = postord (N right) ++ postord (N left) ++ [root]
Here's the error:
* Couldn't match expected type `Int' with actual type `BiTree a'
* In the expression: root
In the second argument of `(++)', namely `[root]'
In the second argument of `(++)', namely
`postord (N left) ++ [root]'
* Relevant bindings include
right :: [BiTree a] (bound at try.hs:21:23)
root :: BiTree a (bound at try.hs:21:18)
left :: BiTree a (bound at try.hs:21:13)
postord :: BiTree a -> [Int] (bound at try.hs:20:1)
|
21 | postord (N (left:root:right)) = postord (N right) ++ postord (N left) ++ [root]
| ^^^^
I don't understand why left:right:root won't bind, and why recalling postord in the list with appends won't compile a list of every node within the right node, left node, and root as it is.
N doesn't have specific left and right children, and it certainly doesn't have any distinguished root value; it just has an arbitrary list of children.
You BiTree only stores values in the leaves. The only thing to do with an N value is map postord on to each child, and concatenate the results into a single list. (As such, there's no real difference between the pre-, in-, and post-order traversals.)
postord :: BiTree a -> [a]
postord (L x) = [x]
postord (N children) = concatMap postord children
Now, if you had a type that did store values in the internal nodes, your type might look like
data BiTree a = L a | N a [BiTree a]
Then your post-order traversal would have to account for the value stored in an internal node, similar to your previous attempt.
postord :: BiTree a -> [a]
postord (L x) = [x]
postord (N v children) = concatMap postord children ++ [v]
Appending a single value to a longer list isn't ideal, but that's a problem for another question.
Don't know if I understood your question, but what about this:
postord :: BiTree a -> [a]
postord (L x) = [x]
postord (N cs) = concatMap postord cs

Check if a binary tree is traversed from left to right in Haskell

I have the following tree and this is how I access the Int values of its nodes and leaves. What I want to do is to write a function "areValuesIncreasing" to check if the values of the nodes/leaves are increasing as the tree is traversed from left to right. Any help would be appreciated.
4 4
/ \ / \
2 3 3 2
/ \ / \ / \ / \
1 3 4 5 - True 1 3 5 4 - False
data Tree = Node Tree Int Tree | Leaf Int deriving Show
treeToInt (Node _ n _) = n
treeToInt (Leaf n ) = n
areValuesIncreasing:: Tree -> Bool
I heavily recommend changing Tree to
data Tree a = Node (Tree a) a (Tree a)
| Leaf a
deriving (...)
and will use this in my answer, but transforming it to your Tree is as easy as setting a ~ Int everywhere and replacing Tree Int with Tree.
Create a list of elements for each layer, and then check that all of those are sorted. Assuming you have a function
foldTree :: (a -> b) -> -- Leaf case
(b -> a -> b -> b) -> -- Node case
Tree a -> b
The leaves produce a list containing a singleton list followed by repeat [], as a leaf is a single element on a level followed by infinitely many empty levels
leafCase x = [x] : repeat []
And the internal nodes concatenate the subtrees' lists' sublists pairwise, while also placing their element in a singleton list on top:
nodeCase l x r = [x] : zipWith (++) l r
Fold this over a Tree to get a list of levels, and cut it off after the last nonempty one:
levels = takeWhile (not . null) . foldTree leafCase nodeCase
Check that each level is sorted:
sorted = all (uncurry (<=)) . (zip <*> tail)
Mix it all up into one function
sortedTree = all sorted . takeWhile (not . null) . levels
where sorted = all (uncurry (<=)) . (zip <*> tail)
levels = foldTree (\l -> [l] : repeat []) (\l x r -> [x] : zipWith (++) l r)
Same thing with recursion-schemes:
makeBaseFunctor ''Tree
-- data TreeF a b = NodeF b a b | LeafF a
-- ...
levelsSorted :: (Recursive t, Foldable (Base t), Ord a) => (Base t [[a]] -> a) -> t -> Bool
levelsSorted get = all sorted . takeWhile (not . null) . levels
where sorted = all (uncurry (<=)) . (zip <*> tail)
levels = cata $ \x -> [get x] : foldr (zipWith (++)) (repeat []) x
levelsSortedTree :: Ord a => Tree a -> Bool
levelsSortedTree = levelsSorted $ \case { LeafF _ x _ -> x; NodeF x -> x }

Depth of a tree (Haskell)

I'm trying to figure out how to calculate the depth of a general tree in Haskell. I can figure out the solution for simple binary trees, but not for general trees with any number of leaves.
Here's the code I have for binary trees.
--depth of a binary tree.
depth :: Tree a -> Int
depth Nil = 0
depth (Node n x1 x2) = 1 + max (depth x1) (depth x2)
How can I modify this for general trees? General trees contain a list of trees, and that is where I am encountering difficulty.
Secondly, I want to turn the tree into a list (so I can do operations such as calculating the sum, etc.)
Again, I can figure it out for binary trees but not for general trees.
--tree into a list.
treeToList:: Tree a -> [a]
treeToList Nil = []
treeToList (Node n x1 x2)
= collapse x1 ++ [n] ++ collapse x2
Use Foldable to get single values out, use Functor to map functions
user2407038's good answer shows you how to write a Foldable instance by hand, which is very good advice, and you can use foldMap not just to make treeToList, but also to make handy other functions.
GHC lets you derive these instances automatically:
{-# LANGUAGE DeriveFunctor, DeriveFoldable #-}
import Data.Monoid
import Data.Foldable
data Tree a = Node a [Tree a]
deriving (Show,Functor,Foldable)
Let's use an example to test this out:
example :: Tree Int
example = Node 3 [Node 2 [], Node 5 [Node 2 [],Node 1 []],Node 10 []]
-- 3
-- |
-- +--+-----+
-- 2 5 10
-- |
-- +--+
-- 2 1
Let's use fmap to multiply everything by 10:
> example
Node 3 [Node 2 [], Node 5 [Node 2 [], Node 1 []], Node 10 []]
> fmap (*10) example
Node 30 [Node 20 [],Node 50 [Node 60 [],Node 10 []],Node 100 []]
Use a Monoid to combine values
A Monoid lets you combine (mappend) values, and has a do-nothing/identity value called mempty.
Lists are a Monoid, with mempty = [] and mappend = (++), numbers are moinoids in more than one way, for example, using (+) (the Sum monoid), using (*) (the Product monoid), using maximum (I had to hand-write the Max monoid).
We'll use foldMap to tag the Ints with what monoid we want to use:
> foldMap Sum example
Sum {getSum = 23}
> foldMap Product example
Product {getProduct = 600}
> foldMap Max example
Max {unMax = 10}
You can define your own monoid however you like - here's how to make the Max monoid:
instance (Ord a,Bounded a) => Monoid (Max a) where
mempty = Max minBound
mappend (Max a) (Max b) = Max $ if a >= b then a else b
The most general fold you can make
In this great question with great answers, Haskell's top asker, MathematicalOrchid asks how to generalise fold to other data types. The answers to the question are great and worth reading.
A generalised fold simply replaces each constructor of the data type with a function and evaluates to get a value.
The hand-rolled way is to look at the types of each of the constructors, and make a function that takes a function argument to match each constructor and an argument for the object itself, and returns a value.
Examples:
[] has two constructors, (:) :: a -> [a] -> [a] and [] :: [a] so
foldList :: (a -> l -> l) -> l -> [a] -> l
foldList useCons useEmpty = f where
f (a:as) = useCons a (f as)
f [] = useEmpty
Either a b has two constructors, Left :: a -> Either a and Right :: a -> Either so
foldEither :: (a -> e) -> (b -> e) -> Either a b -> e
foldEither useLeft useRight = f where
f (Left a) = useLeft a
f (Right b) = useRight b
Generalised fold for your tree
generalFold :: (a -> [t] -> t) -> Tree a -> t
generalFold useNode = f where
f (Node a ts) = useNode a (map f ts)
we can use that to do pretty much anything we want to to a tree:
-- maximum of a list, or zero for an empty list:
maxOr0 [] = 0
maxOr0 xs = maximum xs
height :: Tree a -> Int
height = generalFold maxPlus1 where
maxPlus1 a as = 1 + maxOr0 as
sumTree = generalFold sumNode where
sumNode a as = a + sum as
productTree = generalFold productNode where
productNode a as = a * product as
longestPath = generalFold longest where
longest a as = a + maxOr0 as
Let's test them:
ghci> example
Node 3 [Node 2 [],Node 5 [Node 2 [],Node 1 []],Node 10 []]
ghci> height example
3
ghci> sumTree example -- 3 + sum[2, 5+sum[2,1], 10] = 3+2+5+2+1+10
23
ghci> productTree example -- 3*(2*(5*(2*1))*10) = 3*2*5*2*1*10
600
ghci> longestPath example -- 3 + maximum [2, 5+maximum[2,1], 10]
13
ghci> toList example -- 3 : concat [[2], 5:concat[[2],[1]], [10]]
[3,2,5,2,1,10]
Think about generalizing the pattern to lists:
data Tree a = Node a [Tree a] | Nil
depth Nil = 0
depth (Node _ [a]) = 1 + depth a
depth (Node _ [a,b]) = 1 + max (depth a) (depth b)
depth (Node _ [a,b,c]) = 1 + max (max (depth a) (depth b)) (depth c)
etc...
Well, all you are doing is finding the depth of each subtree (map depth), then finding the maximum of those numbers (maximum):
depth Nil = 0
depth (Node _ a) = 1 + maximum (map depth a)
You can flatten the tree in the same way, just map over the subtrees:
treeToList (Node n a) = n : concat (map treeToList a)
You have to use concat because map collapse returns a list of lists and you just want a list. Alternatively, you can define an instance for the Foldable typeclass and you automatically get toList :: Foldable t => t a -> [a]
import Data.Foldable
import Data.Monoid
instance Foldable Tree where
foldMap f Nil = mempty
foldMap f (Node a n) = f a `mappend` mconcat (map foldMap n)
If you scrutinize the definition of foldMap very carefully, you will see that it is just a more general treeToList, where : is replaced by mappend and [] by mempty. Then it is logical that you can write treeToList in terms of the monoid ([], ++):
data List a = List {getList :: [a]}
instance Monoid (List a) where
mempty = List []
mappend (List a) (List b) = List (a ++ b)
treeToList = getList . foldMap (List . (:[]))
A few pointers:
Take a look at the map function which allows you to apply a function to each element in a list. In your case you want to apply depth to each Tree a in the list of children.
After you get that part you have to find the max depth in the list. Do a google search for "haskell max of list" and you'll find what you need.

Resources