
Hi - I am trying to do Exercise 9.9 in HSOE; and I've come up with an answer that works but I'm not sure if it answers the question properly. The problem is: The Question: ------------- Suppose we define a function "fix" as: fix f = f (fix f) Suppose further we have a recursive function: remainder :: Integer -> Integer -> Integer remainder a b = if a < b then a else remainder (a - b) b Rewrite this function using "fix" so that it's not recursive. My Answer: ---------- wierdFunc x y z = if y - z > z then ((\a b c -> a b c) x (y-z) z) else ((\a b c -> a b c) (\d e -> d) (y-z) z) myRemainder = fix wierdFunc My Question: ------------ Does the ((\a b c -> a b c) x (y-z) z) mean that I've not removed the recursion? I was assuming that I was returning a function that is to be evaluated and not actually doing any recursion. That's why I thought I answered the question. However, I have a headache now and would like another opinion. thanks, -andrew

On Sun, 26 Oct 2003 19:24:26 -0500
"Harris, Andrew"
Hi -
I am trying to do Exercise 9.9 in HSOE; and I've come up with an answer that works but I'm not sure if it answers the question properly. The problem is:
The Question: -------------
Suppose we define a function "fix" as:
fix f = f (fix f)
Suppose further we have a recursive function:
remainder :: Integer -> Integer -> Integer remainder a b = if a < b then a else remainder (a - b) b
Rewrite this function using "fix" so that it's not recursive.
My Answer: ----------
wierdFunc x y z = if y - z > z then ((\a b c -> a b c) x (y-z) z) else ((\a b c -> a b c) (\d e -> d) (y-z) z)
myRemainder = fix wierdFunc
My Question: ------------
Does the ((\a b c -> a b c) x (y-z) z) mean that I've not removed the recursion? I was assuming that I was returning a function that is to be evaluated and not actually doing any recursion. That's why I thought I answered the question. However, I have a headache now and would like another opinion.
Notice that, (\x -> x) a reduces to a, so (\a b c -> a b c) x (y-z) z reduces to x (y-z) z. You can therefore simplify your function quite a bit. wierdFunc x y z = if y-z > z then x (y-z) z else (\d e -> d) (y-z) z and you can still apply that lambda abstraction (beta-reduce) wierdFunc x y z = if y-z > z then x (y-z) z else y-z None of these (except, of course, fix and remainder) are recursive. A recursive function is just one that calls itself. For wierdFunc to be recursive, the identifier wierdFunc would have to occur in the right-hand side of it's definition. This all said, you are making the problem much more difficult than it needs to be. Try matching up your x,y,z's to things in remainder and I think the expected answer will become obvious. Also, you may want to look at the type of fix and wierdFunc (you can use :type in Hugs or GHCi).

Is there a simple transformation that can be applied to all recursive functions to render them non-recursive with fix. ( i suppose there must be or we wouldn't have haskell right? ) ie f :: a -> a f x = .... f .... g :: (a -> a) -> (a -> a) g = \f -> \a ( .... f .... ) fix g = f where .... f ... has the same structure in both cases? On Mon, 27 Oct 2003 11:41 am, Derek Elkins wrote:
On Sun, 26 Oct 2003 19:24:26 -0500
"Harris, Andrew"
wrote: Hi -
I am trying to do Exercise 9.9 in HSOE; and I've come up with an answer that works but I'm not sure if it answers the question properly. The problem is:
The Question: -------------
Suppose we define a function "fix" as:
fix f = f (fix f)
Suppose further we have a recursive function:
remainder :: Integer -> Integer -> Integer remainder a b = if a < b then a else remainder (a - b) b
Rewrite this function using "fix" so that it's not recursive.
My Answer: ----------
wierdFunc x y z = if y - z > z then ((\a b c -> a b c) x (y-z) z) else ((\a b c -> a b c) (\d e -> d) (y-z) z)
myRemainder = fix wierdFunc
My Question: ------------
Does the ((\a b c -> a b c) x (y-z) z) mean that I've not removed the recursion? I was assuming that I was returning a function that is to be evaluated and not actually doing any recursion. That's why I thought I answered the question. However, I have a headache now and would like another opinion.
Notice that, (\x -> x) a reduces to a, so (\a b c -> a b c) x (y-z) z reduces to x (y-z) z. You can therefore simplify your function quite a bit. wierdFunc x y z = if y-z > z then x (y-z) z else (\d e -> d) (y-z) z and you can still apply that lambda abstraction (beta-reduce) wierdFunc x y z = if y-z > z then x (y-z) z else y-z None of these (except, of course, fix and remainder) are recursive. A recursive function is just one that calls itself. For wierdFunc to be recursive, the identifier wierdFunc would have to occur in the right-hand side of it's definition.
This all said, you are making the problem much more difficult than it needs to be. Try matching up your x,y,z's to things in remainder and I think the expected answer will become obvious. Also, you may want to look at the type of fix and wierdFunc (you can use :type in Hugs or GHCi).
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- If people have to choose between freedom and sandwiches, they will take sandwiches. -- Lord Boyd-orr Eats first, morals after. -- Bertolt Brecht, "The Threepenny Opera"

Thomas L. Bevan wrote:
Is there a simple transformation that can be applied to all recursive functions to render them non-recursive with fix.
Suppose you have a LET expression with a set of (possibly mutually recursive) equations such as: let f1 = e1 f2 = e2 ... fn = en in e The following is then equivalent to the above, assuming that g is not free in e or any of the ei: let (f1,...,fn) = fix g g ~(f1,...,fn) = (e1,...,en) in e Note that all recursion introduced by the top-most LET has been removed (or, if you will, concentrated into the one application of fix). This transformation will work even if there is no recursion, and even if some of the fi are not functions (for example they could be recursively defined lazy data structures). For example: main1 = let rem = \a b -> if a < b then a else rem (a - b) b ones = 1 : ones x = 42 in (rem 42 9, take 3 ones, x) is equivalent to: main2 = let (rem,ones,x) = fix g g ~(rem,ones,x) = (\a b -> if a < b then a else rem (a - b) b, 1 : ones, 42 ) in (rem 42 7, take 3 ones, x) and both yield the result (6,[1,1,1],42). -Paul

On Mon, 27 Oct 2003, Paul Hudak wrote:
Thomas L. Bevan wrote:
Is there a simple transformation that can be applied to all recursive functions to render them non-recursive with fix.
Suppose you have a LET expression with a set of (possibly mutually recursive) equations such as:
let f1 = e1 f2 = e2 ... fn = en in e
The following is then equivalent to the above, assuming that g is not free in e or any of the ei:
let (f1,...,fn) = fix g g ~(f1,...,fn) = (e1,...,en) in e
Note that all recursion introduced by the top-most LET has been removed (or, if you will, concentrated into the one application of fix). This transformation will work even if there is no recursion, and even if some of the fi are not functions (for example they could be recursively defined lazy data structures).
This is a very nice technique. As an exercise to the reader I suggest the following program: \being{code} data Tree a = Branch a (Tree (a,a)) | Leaf cross f (a,b) = (f a,f b) main1 = let mapTree :: (a -> b) -> Tree a -> Tree b mapTree = \f tree -> case tree of Branch a t -> Branch (f a) (mapTree (cross f) t) Leaf -> Leaf in mapTree id (Branch 42 Leaf) \end{code] /Josef

Sorry about replying to my own mail. On Mon, 27 Oct 2003, Josef Svenningsson wrote:
On Mon, 27 Oct 2003, Paul Hudak wrote:
Thomas L. Bevan wrote:
Is there a simple transformation that can be applied to all recursive functions to render them non-recursive with fix.
Suppose you have a LET expression with a set of (possibly mutually recursive) equations such as:
let f1 = e1 f2 = e2 ... fn = en in e
The following is then equivalent to the above, assuming that g is not free in e or any of the ei:
let (f1,...,fn) = fix g g ~(f1,...,fn) = (e1,...,en) in e
Note that all recursion introduced by the top-most LET has been removed (or, if you will, concentrated into the one application of fix). This transformation will work even if there is no recursion, and even if some of the fi are not functions (for example they could be recursively defined lazy data structures).
This is a very nice technique. As an exercise to the reader I suggest the following program:
\being{code} data Tree a = Branch a (Tree (a,a)) | Leaf
cross f (a,b) = (f a,f b)
main1 = let mapTree :: (a -> b) -> Tree a -> Tree b mapTree = \f tree -> case tree of Branch a t -> Branch (f a) (mapTree (cross f) t) Leaf -> Leaf in mapTree id (Branch 42 Leaf) \end{code}
I realise I was perhaps a bit dense in my previous mail. It was not my intention to try to sound smart. Sorry for that. Does anyone know how to apply the transformation suggested by Paul Hudak to my program and make it typecheck? Does there exist a type system where the transformed program typechecks? I suppose so but I don't quite know what it would look like. All the best, /Josef

On Tue, Oct 28, 2003 at 11:56:21AM +0100, Josef Svenningsson wrote:
On Mon, 27 Oct 2003, Josef Svenningsson wrote:
This is a very nice technique. As an exercise to the reader I suggest the following program:
\being{code} data Tree a = Branch a (Tree (a,a)) | Leaf
cross f (a,b) = (f a,f b)
main1 = let mapTree :: (a -> b) -> Tree a -> Tree b mapTree = \f tree -> case tree of Branch a t -> Branch (f a) (mapTree (cross f) t) Leaf -> Leaf in mapTree id (Branch 42 Leaf) \end{code}
I realise I was perhaps a bit dense in my previous mail. It was not my intention to try to sound smart. Sorry for that.
Does anyone know how to apply the transformation suggested by Paul Hudak to my program and make it typecheck? Does there exist a type system where the transformed program typechecks? I suppose so but I don't quite know what it would look like.
Polymorphic recursion implies a fix with a rank 3 type. GHC can handle those, but each one needs its own declaration, as in type MapTree = forall a b. (a -> b) -> Tree a -> Tree b fixMT :: (MapTree -> MapTree) -> MapTree fixMT f = f (fixMT f) mapTree' = fixMT (\ (mapTree :: MapTree) -> \f tree -> case tree of Branch a t -> Branch (f a) (mapTree (cross f) t) Leaf -> Leaf)

On Tue, 28 Oct 2003, Ross Paterson wrote:
On Tue, Oct 28, 2003 at 11:56:21AM +0100, Josef Svenningsson wrote:
On Mon, 27 Oct 2003, Josef Svenningsson wrote:
This is a very nice technique. As an exercise to the reader I suggest the following program:
\being{code} data Tree a = Branch a (Tree (a,a)) | Leaf
cross f (a,b) = (f a,f b)
main1 = let mapTree :: (a -> b) -> Tree a -> Tree b mapTree = \f tree -> case tree of Branch a t -> Branch (f a) (mapTree (cross f) t) Leaf -> Leaf in mapTree id (Branch 42 Leaf) \end{code}
I realise I was perhaps a bit dense in my previous mail. It was not my intention to try to sound smart. Sorry for that.
Does anyone know how to apply the transformation suggested by Paul Hudak to my program and make it typecheck? Does there exist a type system where the transformed program typechecks? I suppose so but I don't quite know what it would look like.
Polymorphic recursion implies a fix with a rank 3 type. GHC can handle those, but each one needs its own declaration, as in
type MapTree = forall a b. (a -> b) -> Tree a -> Tree b
fixMT :: (MapTree -> MapTree) -> MapTree fixMT f = f (fixMT f)
mapTree' = fixMT (\ (mapTree :: MapTree) -> \f tree -> case tree of Branch a t -> Branch (f a) (mapTree (cross f) t) Leaf -> Leaf)
I see. It's a little annoying that one would have to write a special fix for every such function. I suppose an impredicative type system whould help here. /Josef

Paul Hudak wrote:
Suppose you have a LET expression with a set of (possibly mutually recursive) equations such as:
let f1 = e1 f2 = e2 ... fn = en in e
The following is then equivalent to the above, assuming that g is not free in e or any of the ei:
let (f1,...,fn) = fix g g ~(f1,...,fn) = (e1,...,en) in e
I'm afraid that is not entirely satisfactory: the above expression uses ... . This implies that we need a meta-language operation -- ellipsis -- to express the mutually recursive fixpoint of several expressions. In the following, we write the polyvariadic fixpoint combinator in pure Haskell98, without any ellipsis construct. The combinator is a translation from Scheme of a polyvariadic fixpoint combinator. The latter is derived in a systematic simplification way. It is different from a polyvariadic Y of Christian Queinnec and of Mayer Goldberg. Here's the polyvaridic Y implemented entirely in Scheme: -- (define (Y* . fl) -- (map (lambda (f) (f)) -- ((lambda (x) (x x)) -- (lambda (p) -- (map -- (lambda (f) -- (lambda () -- (apply f -- (map -- (lambda (ff) -- (lambda y (apply (ff) y))) -- (p p) )))) -- fl))))) Its translation to Haskell couldn't be any simpler due to the non-strict nature of Haskell.
fix':: [[a->b]->a->b] -> [a->b] fix' fl = self_apply (\pp -> map ($pp) fl)
self_apply f = f g where g = f g
That's it. Examples. The common odd-even example:
test1 = (map iseven [0,1,2,3,4,5], map isodd [0,1,2,3,4,5]) where [iseven, isodd] = fix' [fe,fo] fe [e,o] x = x == 0 || o (x-1) fo [e,o] x = x /= 0 && e (x-1)
A more involved example of three mutually-recursive functions: test2 = map (\f -> map f [0,1,2,3,4,5,6,7,8,9,10,11]) fs where fs= fix' [\[triple,triple1,triple2] x-> x==0 || triple2 (x-1), \[triple,triple1,triple2] x-> (x/=0)&&((x==1)|| triple (x-1)), \[triple,triple1,triple2] x-> (x==2)||((x>2)&& triple1 (x-1))]
participants (7)
-
Derek Elkins
-
Harris, Andrew
-
Josef Svenningsson
-
oleg@pobox.com
-
Paul Hudak
-
Ross Paterson
-
Thomas L. Bevan