Haskell function for checking if an element is in a tree, returning depth

I am currently doing a setup for a class where I have to implement a function that checks if an element is in the tree.

It is supposed to return Nothing

when the item is not in the tree and Just

(the depth at which it was found) when it is.

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's 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
}

      

Self-tuning heaps implementation:

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

      

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 assuming to implement the function contains

in the implementation for self-tuning heaps.

I am not allowed to use any helper functions and I have to use the function maybe

.

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 is not working as I am getting parsing error on input |

. I really don't know how to fix this as I used 4 spaces instead of tabs and according to this: https://wiki.haskell.org/Case the syntax is correct ...

I managed to fix it, but I got a type error (1+ (contains x l)

, so it is probably not correct.

Any hint would be appreciated.

EDIT: Thanks to everyone who answered! I really appreciate everyone taking the time to explain their answers in detail.

First of all: there were some more minor bugs, as some of you mentioned in the comments:

I missed one closing parenthesis and accidentally named one argument l1

and another r1

, then used r

and l

. Bugs fixed.

Someone wrote that I don't need to use a lambda function. The problem is that I am using something like:

contains _ Empty = Nothing

      

I am getting the error:

parse the error at the input '_'.

However, lambda functions do not give me any errors regarding the input arguments.

Currently, the only function that works without error 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 hierarchical data

Found: Krom

+3


source to share


3 answers


One way of structuring contains :: Eq a => a -> Tree a -> Maybe Integer

is to first mark each element of your tree with its depth using something like this , then collapse the tree to find the element you are looking for, pulling its depth with it. You can do this without any special code!

Jumping right where this answer left off is here contains

.

contains :: Eq a => a -> Tree a -> Maybe Integer
contains x = fmap fst . find ((== x) . snd) . labelDepths

      

What a whole function! This is a classic style of functional programming: instead of a manual crank recursive tree traversal function, I structured the code as a pipeline of reusable operations. In Haskell, pipelines are built using the composition operator (.)

and are read from left to right. The result labelDepths

is passed to find ((== x) . snd)

, the result of which is then passed to fmap fst

.

labelDepths :: Tree a -> Tree (Integer, a)

I explained in detail in the answer I linked above gives depth to Integer

each element of the input tree.

find :: Foldable t => (a -> Bool) -> t a -> Maybe a

is a standard function that retrieves the first element of a container (such as a tree or a list) that satisfies the verb. In this case, the structure under consideration Foldable

is Tree

, therefore, t ~ Tree

and find :: (a -> Bool) -> Tree a -> Maybe a

. Predicate that I gave find

it ((== x) . snd)

, which returns True

if the second element of its input tuple is equal to x

: find ((== x) . snd) :: Tree (Integer, a) -> Maybe (Integer, a)

. find

works by folding the input structure - checking its elements one at a time until it finds one that matches the predicate. The order in which items are processed is determined by the container Foldable

below.

fmap :: Functor f => (a -> b) -> f a -> f b

is another standard feature. It applies the display function evenly to each element of the container, converting its elements from type a

to type b

. This time, the container in question is the return value find

, which is Maybe

, therefore fmap :: (a -> b) -> Maybe a -> Maybe b

. Display function, which I gave it fst

, which removes the first element of the tuple: fmap fst :: Maybe (Integer, a) -> Maybe Integer

.

So putting everything together, you can see that this is a pretty straight forward implementation of my English description of the above process. We first mark each element of the tree with depth, then find the element that matches the element of interest, then retrieve the depth at which the element was previously marked.


I mentioned above what Tree

a container is Foldable

. In fact, this is not at all the case - there is no instance Foldable

for Tree

. The easiest way to get a copy Foldable

for Tree

is to enable the GHC extension DeriveFoldable

and say the magic words deriving Foldable

.

{-# LANGUAGE DeriveFoldable #-}
data Tree x = Empty | Node x (Tree x) (Tree x) deriving Foldable

      

This auto-generated instance Foldable

will traverse the preposition by traversing the tree from top to bottom. ( x

Counts "to the left of" l

and r

in an expression Node x l r

.) You can customize the derived traversal order by customizing the designer layout Node

.

However, I am assuming this is the purpose and you are not allowed to change the definition Tree

or apply any language extensions. Therefore, you need to manually write your own instance Foldable

following the template at the bottom of this post. Here's an implementation foldr

that does 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 case Node

is interesting. We fold the tree from right to left (like this foldr

) and from bottom to top. First, fold the right subtree z

onto the rightmost leaf. We then use the aggregated result of the right subtree as the seed to fold the left subtree. Finally, we use the result of the addition of all the children Node

as an aggregator to apply to f x

.


I hope you didn't find this answer too advanced! (We'd love to answer any questions you may have.) While the other answers show you well how to write recursive tree traversal functions, I really wanted to give you an idea 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 identify common patterns such as zipping, folding and mapping - you can be very productive and solve problems with very little code.



Foldable instance for binary tree

To create an instance Foldable

, you need to provide a definition of 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 traverses this tree in its path .

ghci> let myTree = Node (Node Leaf 'a' Leaf) 'b' (Node Leaf 'c' Leaf)

--    +--'b'--+
--    |       |
-- +-'a'-+ +-'c'-+
-- |     | |     |
-- *     * *     *

ghci> toList myTree
"abc"

      

The extension DeriveFoldable

allows GHC to generate instances Foldable

based on the type structure. We can change the order of the machine written traversal by adjusting the layout of the constructor Node

.

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"

      

+2


source


This function doesn't have to be a lambda:

contains x t =

      

Adding x

to the case has no purpose, since you will only go back to x

. Instead, you can use pattern matching in the head of the function:

contains _ Empty = Nothing

      

A case Node

has three subsections, where the desired value is less than, greater than, or equal to the value in Node

. If you order them this way, you get symmetry from tests less and more, and you can handle an equal case with otherwise

.



On recusring you will get Maybe Int

to which one you want to add it to. You cannot do it directly because it Int

is inside Maybe

. Usually you should pick up the append, but I suspect this is where the required call should go Maybe

(as unnatural as it sounds):

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, Maybe

(+1)

one could shoot in Maybe

with fmap

(or <$>

):

... = fmap (+1) $ contains ...

      

The use is Maybe

unnatural because it has to be explicitly conveyed Nothing

and also re-wrapped Just

.

0


source


This doesn't work as I am getting parsing error on input |

The previous line is missing a closing parenthesis.

I got a Typ error about (1+ (contains x l))

, so this is probably not correct.

The idea is absolutely correct, the problem is what contains x l

returns Maybe Int

instead Int

, so you cannot directly add to it. You can only add a result when it is Just

. There's a helper function in there that does exactly that, does something for, Just

and saves Nothing

s: 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 would write it like

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

      

0


source







All Articles