help in tree folding

Hi. I'm learning haskell but i'm stuck on a generic tree folding exercise. i must write a function of this type treefoldr::(Eq a,Show a)=>(a->b->c)->c->(c->b->b)->b->Tree a->c Tree has type data (Eq a,Show a)=>Tree a=Void | Node a [Tree a] deriving (Eq,Show) as an example treefoldr (:) [] (++) [] (Node '+' [Node '*' [Node 'x' [], Node 'y' []], Node 'z' []]) must return "+∗xyz" any help? (sorry for my bad english)

On Tue, May 6, 2008 at 6:20 AM, patrik osgnach
Hi. I'm learning haskell but i'm stuck on a generic tree folding exercise. i must write a function of this type treefoldr::(Eq a,Show a)=>(a->b->c)->c->(c->b->b)->b->Tree a->c Tree has type data (Eq a,Show a)=>Tree a=Void | Node a [Tree a] deriving (Eq,Show) as an example treefoldr (:) [] (++) [] (Node '+' [Node '*' [Node 'x' [], Node 'y' []], Node 'z' []]) must return "+∗xyz" any help? (sorry for my bad english)
Functions like this are very abstract, but are also quite nice in that there's basically only one way to write them given the types. What have you tried so far? This function needs to be recursive, so what arguments should it give to its recursive calls, and where should it plug the results? It also helps, as you're writing, to keep meticulous track of the the types of everything you have and the type you need, and that will tell you what you need to write next. Luke

On Tue, May 6, 2008 at 6:20 AM, patrik osgnach
wrote: Hi. I'm learning haskell but i'm stuck on a generic tree folding exercise. i must write a function of this type treefoldr::(Eq a,Show a)=>(a->b->c)->c->(c->b->b)->b->Tree a->c Tree has type data (Eq a,Show a)=>Tree a=Void | Node a [Tree a] deriving (Eq,Show) as an example treefoldr (:) [] (++) [] (Node '+' [Node '*' [Node 'x' [], Node 'y' []], Node 'z' []]) must return "+∗xyz" any help? (sorry for my bad english)
Functions like this are very abstract, but are also quite nice in that there's basically only one way to write them given the types.
What have you tried so far? This function needs to be recursive, so what arguments should it give to its recursive calls, and where should it plug the results?
It also helps, as you're writing, to keep meticulous track of the the types of everything you have and the type you need, and that will tell you what you need to write next.
Luke so far i have tried this
Luke Palmer ha scritto: treefoldr f x g y Void = x treefoldr f x g y (Node a []) = f a y treefoldr f x g y (Node a (t:ts)) = treefoldr f x g (g (treefoldr f x g y t) y) (Node a ts) but it is clearly incorrect. this functions takes as arguments two functions and two zeros (one for the empty tree and one for the empty tree list). thanks for the answer Patrik

On Tue, May 6, 2008 at 8:20 AM, patrik osgnach
Hi. I'm learning haskell but i'm stuck on a generic tree folding exercise. i must write a function of this type treefoldr::(Eq a,Show a)=>(a->b->c)->c->(c->b->b)->b->Tree a->c Tree has type data (Eq a,Show a)=>Tree a=Void | Node a [Tree a] deriving (Eq,Show) as an example treefoldr (:) [] (++) [] (Node '+' [Node '*' [Node 'x' [], Node 'y' []], Node 'z' []]) must return "+∗xyz" any help? (sorry for my bad english)
Having a (Tree a) parameter, where Tree is defined as an algebraic data type, also immediately suggests that you should do some pattern-matching to break treefoldr down into cases: treefoldr f y g z Void = ? treefoldr f y g z (Node x t) = ? -Brent

On Tue, May 6, 2008 at 8:20 AM, patrik osgnach
wrote: Hi. I'm learning haskell but i'm stuck on a generic tree folding exercise. i must write a function of this type treefoldr::(Eq a,Show a)=>(a->b->c)->c->(c->b->b)->b->Tree a->c Tree has type data (Eq a,Show a)=>Tree a=Void | Node a [Tree a] deriving (Eq,Show) as an example treefoldr (:) [] (++) [] (Node '+' [Node '*' [Node 'x' [], Node 'y' []], Node 'z' []]) must return "+∗xyz" any help? (sorry for my bad english)
Having a (Tree a) parameter, where Tree is defined as an algebraic data type, also immediately suggests that you should do some pattern-matching to break treefoldr down into cases:
treefoldr f y g z Void = ? treefoldr f y g z (Node x t) = ?
-Brent so far i have tried
Brent Yorgey ha scritto: treefoldr f x g y Void = x treefoldr f x g y (Node a []) = f a y treefoldr f x g y (Node a (t:ts)) = treefoldr f x g (g (treefoldr f x g y t) y) (Node a ts) but it is incorrect. i can't figure out how to build the recursive call thanks for the answer Patrik

Am Dienstag, 6. Mai 2008 22:40 schrieb patrik osgnach:
Brent Yorgey ha scritto:
On Tue, May 6, 2008 at 8:20 AM, patrik osgnach
wrote:
Hi. I'm learning haskell but i'm stuck on a generic tree folding exercise. i must write a function of this type treefoldr::(Eq a,Show a)=>(a->b->c)->c->(c->b->b)->b->Tree a->c Tree has type data (Eq a,Show a)=>Tree a=Void | Node a [Tree a] deriving (Eq,Show) as an example treefoldr (:) [] (++) [] (Node '+' [Node '*' [Node 'x' [], Node 'y' []], Node 'z' []]) must return "+∗xyz" any help? (sorry for my bad english)
Having a (Tree a) parameter, where Tree is defined as an algebraic data type, also immediately suggests that you should do some pattern-matching to break treefoldr down into cases:
treefoldr f y g z Void = ? treefoldr f y g z (Node x t) = ?
-Brent
so far i have tried treefoldr f x g y Void = x
Yes, nothing else could be done.
treefoldr f x g y (Node a []) = f a y
Not bad. But actually there's no need to treat nodes with and without children differently. Let's see: treefoldr f x g y (Node v ts) should have type c, and it should use v. We have f :: a -> b -> c x :: c g :: c -> b -> b y :: b v :: a. The only thing which produces a value of type c using a value of type a is f, so we must have treefoldr f x g y (Node v ts) = f v someExpressionUsing'ts' where someExpressionUsing'ts' :: b. The only thing we have which produces a value of type b is g, so someExpressionUsing'ts' must ultimately be g something somethingElse. Now take a look at the code and type of foldr, that might give you the idea. Cheers, Daniel
treefoldr f x g y (Node a (t:ts)) = treefoldr f x g (g (treefoldr f x g y t) y) (Node a ts) but it is incorrect. i can't figure out how to build the recursive call thanks for the answer Patrik

Daniel Fischer ha scritto:
Am Dienstag, 6. Mai 2008 22:40 schrieb patrik osgnach:
On Tue, May 6, 2008 at 8:20 AM, patrik osgnach
wrote:
Hi. I'm learning haskell but i'm stuck on a generic tree folding exercise. i must write a function of this type treefoldr::(Eq a,Show a)=>(a->b->c)->c->(c->b->b)->b->Tree a->c Tree has type data (Eq a,Show a)=>Tree a=Void | Node a [Tree a] deriving (Eq,Show) as an example treefoldr (:) [] (++) [] (Node '+' [Node '*' [Node 'x' [], Node 'y' []], Node 'z' []]) must return "+∗xyz" any help? (sorry for my bad english) Having a (Tree a) parameter, where Tree is defined as an algebraic data type, also immediately suggests that you should do some pattern-matching to break treefoldr down into cases:
treefoldr f y g z Void = ? treefoldr f y g z (Node x t) = ?
-Brent so far i have tried
Brent Yorgey ha scritto: treefoldr f x g y Void = x
Yes, nothing else could be done.
treefoldr f x g y (Node a []) = f a y
Not bad. But actually there's no need to treat nodes with and without children differently. Let's see:
treefoldr f x g y (Node v ts)
should have type c, and it should use v. We have f :: a -> b -> c x :: c g :: c -> b -> b y :: b v :: a.
The only thing which produces a value of type c using a value of type a is f, so we must have
treefoldr f x g y (Node v ts) = f v someExpressionUsing'ts'
where
someExpressionUsing'ts' :: b.
The only thing we have which produces a value of type b is g, so someExpressionUsing'ts' must ultimately be g something somethingElse. Now take a look at the code and type of foldr, that might give you the idea.
Cheers, Daniel
treefoldr f x g y (Node a (t:ts)) = treefoldr f x g (g (treefoldr f x g y t) y) (Node a ts) but it is incorrect. i can't figure out how to build the recursive call thanks for the answer Patrik
thanks for the tip. so, if i have understood correctly i have to wirite something like: treefoldr f x g y (Node a ts) = f a (g (treefoldr f x g y (head ts)) (g (treefoldr f x g y (head (tail ts)) (g ... it looks like a list foldr so... treefoldr f x g y Void = x treefoldr f x g y (Node a ts) = f a (foldr (g) y (map (treefoldr f x g y) ts)) it seems to work. i'm not yet sure it is correct but is better than nothing thanks to you all. now i will try to write a treefoldl

On Wed, May 7, 2008 at 6:28 AM, patrik osgnach
Daniel Fischer ha scritto:
Am Dienstag, 6. Mai 2008 22:40 schrieb patrik osgnach:
Brent Yorgey ha scritto:
On Tue, May 6, 2008 at 8:20 AM, patrik osgnach < patrik.osgnach@gmail.com>
wrote:
Hi. I'm learning haskell but i'm stuck on a generic tree folding exercise. i must write a function of this type treefoldr::(Eq a,Show a)=>(a->b->c)->c->(c->b->b)->b->Tree a->c Tree has type data (Eq a,Show a)=>Tree a=Void | Node a [Tree a] deriving (Eq,Show) as an example treefoldr (:) [] (++) [] (Node '+' [Node '*' [Node 'x' [], Node 'y' []], Node 'z' []]) must return "+∗xyz" any help? (sorry for my bad english)
Having a (Tree a) parameter, where Tree is defined as an algebraic data type, also immediately suggests that you should do some pattern-matching to break treefoldr down into cases:
treefoldr f y g z Void = ? treefoldr f y g z (Node x t) = ?
-Brent
so far i have tried treefoldr f x g y Void = x
Yes, nothing else could be done.
treefoldr f x g y (Node a []) = f a y
Not bad. But actually there's no need to treat nodes with and without children differently. Let's see:
treefoldr f x g y (Node v ts)
should have type c, and it should use v. We have f :: a -> b -> c x :: c g :: c -> b -> b y :: b v :: a.
The only thing which produces a value of type c using a value of type a is f, so we must have
treefoldr f x g y (Node v ts) = f v someExpressionUsing'ts'
where
someExpressionUsing'ts' :: b.
The only thing we have which produces a value of type b is g, so someExpressionUsing'ts' must ultimately be g something somethingElse. Now take a look at the code and type of foldr, that might give you the idea.
Cheers, Daniel
treefoldr f x g y (Node a (t:ts)) = treefoldr f x g (g (treefoldr f x g
y t) y) (Node a ts) but it is incorrect. i can't figure out how to build the recursive call thanks for the answer Patrik
thanks for the tip.
so, if i have understood correctly i have to wirite something like: treefoldr f x g y (Node a ts) = f a (g (treefoldr f x g y (head ts)) (g (treefoldr f x g y (head (tail ts)) (g ... it looks like a list foldr so... treefoldr f x g y Void = x treefoldr f x g y (Node a ts) = f a (foldr (g) y (map (treefoldr f x g y) ts)) it seems to work. i'm not yet sure it is correct but is better than nothing thanks to you all. now i will try to write a treefoldl
If it typechecks and you have used all the parameters, then it is probably correct! =) That may sound trite, but it is often true. -Brent
participants (4)
-
Brent Yorgey
-
Daniel Fischer
-
Luke Palmer
-
patrik osgnach