How to seperate list elements as Char or Float - haskell

When I take a mixed tree from char and float I have to seperate them as a Float or Character in haskell and add them to the specific list I tried to write something as you can see below;
I tried to take a as [a] in the else part but it gives error too.
data BETree = Leaf Float | Node Char BETree BETree deriving (Show, Ord, Eq)
charList :: [Char]
charList = []
floatList :: [Float]
floatList = []
toList :: BETree -> ([Float], [Char])
toList (Node a l r) = if (a :: Char ) then (charList ++ [a])
else (floatList ++ a)
I expect to entered values to seperate for floatList and charList however I get errors like this;
Couldn't match expected type ‘[[Char]]’ with actual type ‘Char’
OR
vice versa

There are a couple of aspects of Haskell that you haven't mastered yet, and they're causing you some difficulty.
First, as you probably know, Haskell takes its types very seriously. It's a strongly typed language, so that means that the whole concept of searching through a data structure to find values of a particular type is the wrong way of thinking about this problem. The definition of BETree is:
data BETree = Leaf Float | Node Char BETree BETree deriving (Show, Ord, Eq)
which says that this structure consists of Leafs that contain a Float and internal Nodes that contain a Char. So, if you want to find all the Char values, you don't check the types, you just look for the Nodes. They will all contain Chars and can't contain anything else, by the definition of BETree. In other words, in your function definition:
toList (Node a l r) = ...
you don't need to try to check the type of a -- it's guaranteed to be Char by the definition of Node in the BETree definition. If you separately write a definition:
toList (Leaf x) = ...
then you're similarly guaranteed that x is a Float, and you don't need to check any types.
Second, Haskell normally works with immutable values. This means that, unlike in most other languages, you usually don't start by creating an empty list and then trying to add elements to it in a separate function. Instead, you usually write recursive functions that return the "list so far", which they generate by adding an element (or elements) to the list returned by recursively calling themselves. As a simple example, to write a function that builds up the list of all positive integers in an input list, you'd write:
positiveInts :: [Int] -> [Int]
positiveInts (x:xs) | x > 0 = x : positiveInts xs -- add "x" to list from recursive call
| otherwise = positiveInts xs -- drop "x"
positiveInts [] = []
So. here's how it might work for your problem, starting with the simpler problem of just building the floatList:
toFloatList :: BETree -> [Float]
toFloatList (Leaf x) = [x] -- x is guaranteed to be a Float, so return it
toFloatList (Node _a l r) = -- _a can't be a float, so ignore it
toFloatList l ++ toFloatList r -- but recurse to find more Floats in Leafs
And test it:
> toFloatList (Node 'x' (Leaf 1.0) (Node 'y' (Leaf 3.0) (Leaf 4.0)))
[1.0,3.0,4.0]
>
Building just the charList is only slightly more complicated:
toCharList :: BETree -> [Char]
toCharList (Leaf _x) = [] -- x is guaranteed to be a Float, so no Chars here
toCharList (Node a l r) = -- "a" is a Char
toCharList l ++ [a] ++ toCharList r -- recurse and put "a" in the middle
and testing it:
> toCharList (Node 'x' (Leaf 1.0) (Node 'y' (Leaf 3.0) (Leaf 4.0)))
"xy"
> "xy" == ['x','y']
True
>
In Haskell, the list of Chars ['x','y'] is equivalent to the string "xy" which is why it gets printed this way.
Now, the easiest way to define toList is:
toList :: BETree -> ([Float], [Char])
toList bet = (toFloatList bet, toCharList bet)
This traverses the tree twice. If you want to build both lists together in a single traversal, things get significantly more complicated:
toList' :: BETree -> ([Float], [Char])
toList' (Leaf x) = ([x],[]) -- easy, since Leaf contains only one Float
toList' (Node a l r) = -- Nodes are harder
let (fl1, cl1) = toList' l -- lists from the left branch
(fl2, cl2) = toList' r -- lists from the right branch
in (fl1 ++ fl2, cl1 ++ [a] ++ cl2) -- combine with our Char "a"
and the test:
> toList (Node 'x' (Leaf 1.0) (Node 'y' (Leaf 3.0) (Leaf 4.0)))
([1.0,3.0,4.0],"xy")
> toList' (Node 'x' (Leaf 1.0) (Node 'y' (Leaf 3.0) (Leaf 4.0)))
([1.0,3.0,4.0],"xy")
>

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.

General Tree in Haskell = Rose Tree? Postoder for a rose tree?

I was supposed to create a data structure for a Tree, where every Node has an undefined amount of branches. I am guessing this will be a rose tree.
data GTree a = Node a [GTree a]
Now I am supposed to write a postorderG function that will give me a list of all my elements in my general in a postorder sequence
I wrote this but it does not seem right... Could someone help me?
postorderG :: GTree a -> [a]
postorderG (Node x l r) = postorder l ++ postorder r ++ [GTree x]
GTree is a type constructor, not a data constructor; a tree would be created with Node x [], not GTree x.
However, you don't need to create a tree at all here. You just need a the value stored at the root of the input tree for the final list in the return value.
postorderG :: GTree a -> [a]
postorderG (Node x ch) = concatMap postorderG ch -- [a]
++ [x] -- [a], not [GTree a]
If you wanted to, you could create a singleton tree to append to ch, the apply postOrderG to each child and the new singleton in order.
postorderG (Node x ch) = concatMap postorderG (ch ++ [Node x []])
Taking advantage of the [] monad instead of using concatMap, the RHS would look like either
(ch >>= postorderG) ++ [x]
or
(ch ++ [Node x []]) >>= postorderG

Haskell Function for checking if element is in Tree, returning Depth

I am currently doing an assigment for a class in which I have to implement a function which checks if an element is in a tree.
It is supposed to return Nothing when the element is not in the tree and Just (depth at which it was found) when it is.
An example:
sample1
##1
#3 2
###7 5 6 4
- contains 6 sample1 returns Just 2
- contains 1 sample1 returns Just 0
- contains 2 sample1 returns Just 1
- contains 8 sample1 returns Nothing
Here is what we are given:
Heap functional data structure:
module Fdata.Heap where
-- A signature for min-heaps
data Heap e t = Heap {
empty :: t e,
insert :: e -> t e -> t e,
findMin :: t e -> Maybe e,
deleteMin :: t e -> Maybe (t e),
merge :: t e -> t e -> t e,
contains :: e -> t e -> Maybe Int
}
An implementation of self-adjusting heaps:
import Fdata.Heap
import Fdata.Tree
-- An implementation of self-adjusting heaps
heap :: (Eq e, Ord e) => Heap e Tree
heap = Heap {
empty = Empty,
insert = \x t -> merge' (Node x Empty Empty) t,
findMin = \t -> case t of
Empty -> Nothing
(Node x _ _) -> Just x,
deleteMin = \t -> case t of
Empty -> Nothing
(Node _ l r) -> Just (merge' r l),
merge = \l r -> case (l, r) of
(Empty, t) -> t
(t, Empty) -> t
(t1#(Node x1 l1 r1), t2#(Node x2 l2 r2)) ->
if x1 <= x2
then Node x1 (merge' t2 r1) l1
else Node x2 (merge' t1 r2) l2,
contains = \x t -> case (x,t) of
(x,Empty)-> Nothing
(x,tx#(Node x1 l1 r1) ->
|x==x1 = Just 0
|x>x1 = (1+ (contains x l)
|x<x1 = (1+ (contains x r)
}
where
merge' = merge heap
The tree implementation
module Fdata.Tree where
import Fdata.Heap
data Tree x
= Empty
| Node x (Tree x) (Tree x)
deriving (Eq, Show)
leaf x = Node x Empty Empty
-- Convert a list to a heap
list2heap :: Heap x t -> [x] -> t x
list2heap i = foldl f z
where
f = flip $ insert i
z = empty i
-- Convert a heap to a list
heap2list :: Heap x t -> t x -> [x]
heap2list i t
= case (findMin i t, deleteMin i t) of
(Nothing, Nothing) -> []
(Just x, Just t') -> x : heap2list i t'
I am supposed to implement the contains function in the implementation for self-adjusting heaps.
I am not allowed to use any helper functions and I am supposed to use the maybe function.
My current implementation:
contains = \x t -> case (x,t) of
(x,Empty) -> Nothing
(x,tx#(Node x1 l1 r1))
|x==x1 -> Just 0
|x>x1 -> (1+ (contains x l1)
|x<x1 -> (1+ (contains x r1)
This does not work, since I get a parse error on input |.
I really dont know how to fix this since I did use 4 spaces instead of tabs and according to this: https://wiki.haskell.org/Case
the syntax is correct...
I once managed to fix this, but I got a type error about (1+ (contains x l), so this probably is not correct.
Any hint would be appreciated.
EDIT:
Thanks to everyone who answered!
Really appreciate that everyone took the time to explain their answers in great detail.
First of all:
there were some smaller mistakes, as pointed out by some of you in the comments:
I missed one closing parenthesis and accidentially named one argument l1 and another r1 and afterwards used r and l.
Fixed both mistakes.
Someone wrote that I do not need to use a lambda function. The problem is when I use something like:
contains _ Empty = Nothing
I get the error:
parse Error on input '_'.
However, lambda functions do not give me any errors about the input arguments.
Currently the only function that works without any errors is:
contains = \e t -> case (e,t) of
(_,Empty) -> Nothing
(e , Node x t1 t2) ->
if e == (head (heap2list heap (Node x t1 t2)))
then Just 0
else if (fmap (+1) (contains heap e t1))== Nothing
then (fmap (+1) (contains heap e t2))
else (fmap (+1) (contains heap e t1))
Found at:
Counting/Getting "Level" of a hierarchical data
Found by:Krom
One way of structuring contains :: Eq a => a -> Tree a -> Maybe Integer is to first label each element in your tree with its depth, using something like this, then fold the tree to find the element you're looking for, pulling its depth out with it. You can do this without very much code!
Jumping right in where this answer left off, here's contains.
contains :: Eq a => a -> Tree a -> Maybe Integer
contains x = fmap fst . find ((== x) . snd) . labelDepths
That's the whole function! This is classic functional programming style: rather than hand-crank a bespoke recursive tree traversal function I've structured the code as a pipeline of reusable operations. In Haskell pipelines are constructed using the composition operator (.) and are read from left to right. The result of labelDepths is passed to find ((== x) . snd), whose result is then passed to fmap fst.
labelDepths :: Tree a -> Tree (Integer, a), which I've explained in detail in the answer I linked above, attaches an Integer depth to each element of the input tree.
find :: Foldable t => (a -> Bool) -> t a -> Maybe a is a standard function which extracts the first element of a container (like a tree, or a list) that satisfies a predicate. In this instance, the Foldable structure in question is a Tree, so t ~ Tree and find :: (a -> Bool) -> Tree a -> Maybe a. The predicate I've given to find is ((== x) . snd), which returns True if the second element of its input tuple equals x: find ((== x) . snd) :: Tree (Integer, a) -> Maybe (Integer, a). find works by folding the input structure - testing its elements one at a time until it finds one that matches the predicate. The order in which elements are processed is defined by the container's Foldable instance, of which more below.
fmap :: Functor f => (a -> b) -> f a -> f b is another standard function. It applies a mapping function uniformly to each element of a container, transforming its elements from type a to type b. This time the container in question is the return value of find, which is a Maybe, so fmap :: (a -> b) -> Maybe a -> Maybe b. The mapping function I've supplied is fst, which extracts the first element of a tuple: fmap fst :: Maybe (Integer, a) -> Maybe Integer.
So putting it all together, you can see that this is a fairly direct implementation of my English description of the process above. First we label every element in the tree with its depth, then we find an element which matches the item we're looking for, then we extract the depth with which the element was previously labelled.
I mentioned above that Tree is a Foldable container. In fact, this isn't the case quite yet - there's no instance of Foldable for Tree. The easiest way to get a Foldable instance for Tree is to turn on the DeriveFoldable GHC extension and utter the magic words deriving Foldable.
{-# LANGUAGE DeriveFoldable #-}
data Tree x = Empty | Node x (Tree x) (Tree x) deriving Foldable
This automatically-implemented instance of Foldable will perform a preorder traversal, processing the tree in a top-down fashion. (x is considered to be "to the left of" l and r in the expression Node x l r.) You can adjust the derived traversal order by adjusting the layout of the Node constructor.
That said, I'm guessing that this is an assignment and you're not allowed to modify the definition of Tree or apply any language extensions. So you'll need to hand-write your own instance of Foldable, following the template at the bottom of this post. Here's an implementation of foldr which performs a preorder traversal.
instance Foldable Tree where
foldr f z Empty = z
foldr f z (Node x l r) = f x (foldr f (foldr f z r) l)
The Node case is the interesting one. We fold the tree from right to left (since this is a foldr) and from bottom to top. First we fold the right subtree, placing z at the rightmost leaf. Then we use the aggregated result of the right subtree as the seed for folding the left subtree. Finally we use the result of folding all of the Node's children as the aggregator to apply to f x.
Hopefully you didn't find this answer too advanced! (Happy to answer any questions you have.) While the other answers do a good job of showcasing how to write recursive tree traversal functions, I really wanted to give you a glimpse of the real power of functional programming. When you think at a higher level - breaking down a problem into its component parts, structuring operations as pipelines, and learning to spot common patterns like zipping, folding and mapping - you can be very productive and solve problems with very little code.
An instance of Foldable for a binary tree
To instantiate Foldable you need to provide a definition for at least foldMap or foldr.
data Tree a = Leaf
| Node (Tree a) a (Tree a)
instance Foldable Tree where
foldMap f Leaf = mempty
foldMap f (Node l x r) = foldMap f l `mappend` f x `mappend` foldMap f r
foldr f acc Leaf = acc
foldr f acc (Node l x r) = foldr f (f x (foldr f acc r)) l
This implementation performs an in-order traversal of the tree.
ghci> let myTree = Node (Node Leaf 'a' Leaf) 'b' (Node Leaf 'c' Leaf)
-- +--'b'--+
-- | |
-- +-'a'-+ +-'c'-+
-- | | | |
-- * * * *
ghci> toList myTree
"abc"
The DeriveFoldable extension allows GHC to generate Foldable instances based on the structure of the type. We can vary the order of the machine-written traversal by adjusting the layout of the Node constructor.
data Inorder a = ILeaf
| INode (Inorder a) a (Inorder a) -- as before
deriving Foldable
data Preorder a = PrLeaf
| PrNode a (Preorder a) (Preorder a)
deriving Foldable
data Postorder a = PoLeaf
| PoNode (Postorder a) (Postorder a) a
deriving Foldable
-- injections from the earlier Tree type
inorder :: Tree a -> Inorder a
inorder Leaf = ILeaf
inorder (Node l x r) = INode (inorder l) x (inorder r)
preorder :: Tree a -> Preorder a
preorder Leaf = PrLeaf
preorder (Node l x r) = PrNode x (preorder l) (preorder r)
postorder :: Tree a -> Postorder a
postorder Leaf = PoLeaf
postorder (Node l x r) = PoNode (postorder l) (postorder r) x
ghci> toList (inorder myTree)
"abc"
ghci> toList (preorder myTree)
"bac"
ghci> toList (postorder myTree)
"acb"
This function doesn't need to be a lambda:
contains x t =
Adding x to the case serves no purpose, since you only match it back to x. You can instead use pattern matching in the function head:
contains _ Empty = Nothing
The Node case has three sub-cases, where the value being searched for is less-than, greater-than, or equal to the value in the Node. If you order them that way, you get a symmetry from the less-than and greater-than tests, and can handle the equal case with an otherwise.
When recusring, you are going to get a Maybe Int, to which you want to add one. You can't do that directly because the Int is inside the Maybe. Normally, you would lift the addition, but I suspect that this is where the required call to maybe should go (however unnatural it may seem):
contains x (Node x' l r) | x < x' = maybe Nothing (Just . (+1)) $ contains x l
| x > x' = maybe Nothing (Just . (+1)) $ contains x r
| otherwise = Just 0
Instead of using maybe, the (+1) could have been lifted into the Maybe with fmap (or <$>):
... = fmap (+1) $ contains ...
Using maybe is unnatural because it has to explicitly pass the Nothing, and also re-wrap the Just.
This does not work, since I get a parse error on input |
Your previous line misses a closing parenthesis.
I got a Typ error about (1+ (contains x l)), so this probably is not correct.
The idea is totally correct, the issue is that contains x l returns a Maybe Int instead of an Int so you cannot directly add to that. You can only add to the result when it's a Just. There's a helper function that does exactly that, do something to Justs and keep Nothings: fmap (from Functor).
contains = \x t -> case (x,t) of
(x,Empty)-> Nothing
(x,tx#(Node x1 l1 r1))
|x==x1 -> Just 0
|x>x1 -> fmap (1+) (contains x l)
|x<x1 -> fmap (1+) (contains x r)
Btw, I'd write this as
contains x Empty = Nothing
contains x (Node v l r) = if x == v
then Just 0
else fmap (+1) $ contains x $ if x > v then l else r

Haskell - Sum values in a tree

My tree looks like this, a tree which at each node can or cannot have an integer:
data Tree = Empty | Node (Maybe Integer) Tree Tree deriving Show
I want to sum all the values in the tree, not including Nothing values and if tree is not empty but has only Nothing values, just return Nothing, or empty tree is 0. These cases I understand how to.
I want thinking depth first traversal would be best, or just some basic traversal in general, but struggling on how to implement it elegantly.
treeValues :: Tree -> Maybe Integer
You can make your Tree a Foldable instance, and you get many functions for free, including sum:
sum :: (Foldable t, Num a) => t a -> a Source
The sum function computes the sum of the numbers of a structure.
But you need to make your Tree a parametric type:
data Tree a = Empty | Node (Maybe a) Tree Tree
Also, with GHC 7.10, almost all Prelude functions will use Foldable and Traversable typeclasses instead of lists, and then you can use them freely for your tree, if you implement those typeclasses.
You already know how to sum lists, so you could transform your tree into a list first:
> toList :: Tree -> [Integer]
> toList Empty = []
> toList (Node a l r) = maybeToList a ++ toList l ++ toList r
> where maybeToList (Just x) = [x]
> maybeToList Nothing = []
Now, you want to differ between an empty tree (Empty) and a tree that contains only Nothing. Since toList filters all Nothing values, this boils down to
> sumTree :: Tree -> Maybe Integer
> sumTree Empty = Just 0
> sumTree tree = case toList tree of
> [] -> Nothing -- all values in the tree are Nothing
> xs -> Just $ sum xs -- some were Just x
But wait, there's more!
sumTree isn't that nice yet. What if we want to compute the product of a Tree? Hm. Well, we can take a tree, transform it to a list, and use… a folding function!
> type I = Integer -- otherwise the lines get ridiculously long
>
> foldrTree' :: (I -> I -> I) -> I -> Tree -> Maybe I
> foldrTree' _ init Empty = init
> foldrTree' f init tree = case toList tree of
> [] -> Nothing
> xs -> Just $ foldr f init xs
> -- ^^^^^
Now we can take any (Integer -> Integer -> Integer) and produce a single value, as long as our operation is associative:
> productTree :: Tree -> Maybe Integer
> productTree = foldrTree' (*) 1
>
> sumTree' :: Tree -> Maybe Integer
> sumTree' = foldrTree' (+) 0
Here's a hint:
data Tree a = Empty | Node a (Tree a) (Tree a)
reduce :: (a -> r -> r -> r) -> r -> Tree a -> r
reduce f z = go
where
go Empty = z
go (Node x l r) = f x (go l) (go r)
Regarding the above solutions and comments plus lyah and Brent Yorgeys advice I compiled the following proposal (try as you might like in ghci):
:set -XDeriveFoldable -XDeriveFunctor
:m + Data.Foldable Data.Monoid
data Tree a = Empty | Node (Maybe a) (Tree a) (Tree a) deriving (Show, Functor, Foldable)
let tree :: Tree Integer ; tree = Node Nothing (Node (Just 42) Empty Empty) (Node Nothing Empty Empty)
foldMap Sum tree
It though returns only 0 in both cases only Nothing values given and tree is Empty but I hope it gives a hint later for learners like me.

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