iterative algorithms: how to do it in Haskell?

Hi, I am a newbie learning Haskell. I have used languages with functional features before (R, Scheme) but not purely functional ones without side-effects. Most of the programming I do is numerical (I am an economist). I would like to know how to implement the iterative algorithm below in Haskell. f is an a->a function, and there is a stopping rule goOn(a,anext) :: a a -> Bool which determines when to stop. The algorithm looks like this (in imperative pseudocode): a = ainit while (true) { anext <- f(a) if (goOn(a,anext)) a <- anext else stop and return anext } For example, f can be a contraction mapping and goOn a test based on the metric. I don't know how to do this in a purely functional language, especially if the object a is large and I would like it to be garbage collected if the iteration goes on. Thank you, Tamas

Tamas K Papp wrote:
Hi,
I am a newbie learning Haskell. I have used languages with functional features before (R, Scheme) but not purely functional ones without side-effects.
Most of the programming I do is numerical (I am an economist). I would like to know how to implement the iterative algorithm below in Haskell.
f is an a->a function, and there is a stopping rule goOn(a,anext) :: a a -> Bool which determines when to stop. The algorithm looks like this (in imperative pseudocode):
a = ainit
while (true) { anext <- f(a) if (goOn(a,anext)) a <- anext else stop and return anext }
For example, f can be a contraction mapping and goOn a test based on the metric. I don't know how to do this in a purely functional language, especially if the object a is large and I would like it to be garbage collected if the iteration goes on.
Thank you,
Tamas _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
iterUntil :: (a -> a -> Bool) -> (a -> a) -> a -> a iterUntil goOn f aInit = let loop a = let a' = f a in if goOn a a' then loop a' -- tail recursive (so "a" will be collected) else a' in loop aInit -- Chris

Chris Kuklewicz wrote:
Tamas K Papp wrote:
Hi,
I am a newbie learning Haskell. I have used languages with functional features before (R, Scheme) but not purely functional ones without side-effects.
Most of the programming I do is numerical (I am an economist). I would like to know how to implement the iterative algorithm below in Haskell.
f is an a->a function, and there is a stopping rule goOn(a,anext) :: a a -> Bool which determines when to stop. The algorithm looks like this (in imperative pseudocode):
a = ainit
while (true) { anext <- f(a) if (goOn(a,anext)) a <- anext else stop and return anext }
For example, f can be a contraction mapping and goOn a test based on the metric. I don't know how to do this in a purely functional language, especially if the object a is large and I would like it to be garbage collected if the iteration goes on.
Thank you,
Tamas _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
iterUntil :: (a -> a -> Bool) -> (a -> a) -> a -> a iterUntil goOn f aInit = let loop a = let a' = f a in if goOn a a' then loop a' -- tail recursive (so "a" will be collected) else a' in loop aInit
In Haskell you can do this iterUntil :: (a -> a -> Bool) -> (a -> a) -> a -> a iterUntil goOn f a | goOn a anext = iterUntil goOn f anext | otherwise = anext where anext = f a

You might use the Prelude function until: until :: (a -> Bool) -> (a -> a) -> a -> a until (> 3) (+ 2) 0 = 4 or for your purpose: until (\ a -> not (goOn(a, f(a))) f ainit http://www.haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v%3A... http://www.haskell.org/onlinereport/prelude-index.html http://www.haskell.org/onlinereport/standard-prelude.html#$vuntil HTH Christian Tamas K Papp schrieb:
Hi,
I am a newbie learning Haskell. I have used languages with functional features before (R, Scheme) but not purely functional ones without side-effects.
Most of the programming I do is numerical (I am an economist). I would like to know how to implement the iterative algorithm below in Haskell.
f is an a->a function, and there is a stopping rule goOn(a,anext) :: a a -> Bool which determines when to stop. The algorithm looks like this (in imperative pseudocode):
a = ainit
while (true) { anext <- f(a) if (goOn(a,anext)) a <- anext else stop and return anext }
For example, f can be a contraction mapping and goOn a test based on the metric. I don't know how to do this in a purely functional language, especially if the object a is large and I would like it to be garbage collected if the iteration goes on.
Thank you,
Tamas

Tamas K Papp wrote:
f is an a->a function, and there is a stopping rule goOn(a,anext) :: a a -> Bool which determines when to stop. The algorithm looks like this (in imperative pseudocode):
a = ainit
while (true) { anext <- f(a) if (goOn(a,anext)) a <- anext else stop and return anext }
For example, f can be a contraction mapping and goOn a test based on the metric. I don't know how to do this in a purely functional language, especially if the object a is large and I would like it to be garbage collected if the iteration goes on.
The idea is to make the iteration variables arguments to a tail-recursive function: let foo a | goOn a anext = foo anext | otherwise = anext where anext = f a in foo ainit

G'day Tamas.
Quoting Tamas K Papp
f is an a->a function, and there is a stopping rule goOn(a,anext) :: a a -> Bool which determines when to stop. The algorithm looks like this (in imperative pseudocode):
a = ainit
while (true) { anext <- f(a) if (goOn(a,anext)) a <- anext else stop and return anext }
Here are a couple more suggestions. First, this function scans an infinite list and stops when p x1 x2 is true for two adjacent elements x1 and x2: findFixpoint p (x1:xs@(x2:_)) | p x1 x2 = x2 | otherwise = findFixpoint p xs Then you just need to pass it [ainit, f ainit, f (f ainit), ...]: findFixpoint dontGoOn (iterate f ainit) Note that the function to pass to findFixpoint here is the condition to use to _stop_. If you're comfortable with monads, it's possible to directly simulate complex imperative control flow. It's not recommended to do this unless the flow is very complex, but here we are for the record: import Control.Monad.Cont -- I used a Newton-Raphson square root evaluation for testing, -- but it has the same structure as your algorithm. mysqrt :: Double -> Double mysqrt x = runCont (callCC loop) id where ainit = x * 0.5 f x = 0.5 * (a + x/a) goOn a1 a2 = abs (a1 - a2) > 1e-5 loop break = loop' ainit where loop' a = do let anext = f a if goOn a anext then loop' anext else break anext callCC defines a point outside the loop that you can "break" to. You simply call that function (called a "continuation") and the loop is broken. Cheers, Andrew Bromage

ajb@spamcop.net wrote:
G'day Tamas.
Quoting Tamas K Papp
: f is an a->a function, and there is a stopping rule goOn(a,anext) :: a a -> Bool which determines when to stop. The algorithm looks like this (in imperative pseudocode):
a = ainit
while (true) { anext <- f(a) if (goOn(a,anext)) a <- anext else stop and return anext }
Here are a couple more suggestions.
First, this function scans an infinite list and stops when p x1 x2 is true for two adjacent elements x1 and x2:
findFixpoint p (x1:xs@(x2:_)) | p x1 x2 = x2 | otherwise = findFixpoint p xs
Then you just need to pass it [ainit, f ainit, f (f ainit), ...]:
findFixpoint dontGoOn (iterate f ainit)
Note that the function to pass to findFixpoint here is the condition to use to _stop_.
The compiler may not deforest that list, so creating the list may be a small overhead of this method.
If you're comfortable with monads, it's possible to directly simulate complex imperative control flow. It's not recommended to do this unless the flow is very complex, but here we are for the record:
import Control.Monad.Cont
-- I used a Newton-Raphson square root evaluation for testing, -- but it has the same structure as your algorithm. mysqrt :: Double -> Double mysqrt x = runCont (callCC loop) id where ainit = x * 0.5
f x = 0.5 * (a + x/a)
goOn a1 a2 = abs (a1 - a2) > 1e-5
loop break = loop' ainit where loop' a = do let anext = f a if goOn a anext then loop' anext else break anext
callCC defines a point outside the loop that you can "break" to. You simply call that function (called a "continuation") and the loop is broken.
Cheers, Andrew Bromage
Note that "f x" should be "f a" above. But I like it. My version of the above looks like
import Control.Monad.Cont
mysqrt :: Double -> Double mysqrt x = doWhile goOn f aInit where aInit = x * 0.5 f a = 0.5 * (a + x/a) goOn a1 a2 = abs (a1 - a2) > 1e-5
doWhile :: (a -> a -> Bool) -> (a -> a) -> a -> a doWhile goOn f x0 = runCont (callCC withBreak) id where withBreak break = let loop x = do let x' = f x when (not (goOn x x')) (break x') loop x' in loop x0

G'day all.
Quoting Chris Kuklewicz
The compiler may not deforest that list, so creating the list may be a small overhead of this method.
And in return, you get: - Code that is smaller than the imperative version, AND - a reusable function, making the next incarnation of an algorithm like this even shorter. For most interesting cases, the cost of f and goOn will surely dominate anyway.
Note that "f x" should be "f a" above.
Yes, you're right. I abstracted out "f" after testing and before posting. Cheers, Andrew Bromage

On Thu, Aug 17, 2006 at 01:23:19AM -0400, ajb@spamcop.net wrote:
G'day all.
Quoting Chris Kuklewicz
: The compiler may not deforest that list, so creating the list may be a small overhead of this method.
And in return, you get:
- Code that is smaller than the imperative version, AND - a reusable function, making the next incarnation of an algorithm like this even shorter.
For most interesting cases, the cost of f and goOn will surely dominate anyway.
Note that "f x" should be "f a" above.
Yes, you're right. I abstracted out "f" after testing and before posting.
Chris, Christian, Andrew, Antti-Juhani and Ivan, Thanks for your answers, they were very enlightening (though it will take some time to understand everything). Haskell looks even more elegant than Scheme... Best, Tamas

Hi, Here is a little thing I came up with to simulate the construct "for x:= n1 to n2" and "for x:=n1 to n2 by n3" from purely imperative world to use in Haskell, I call the functions fromto and fromtoby.. they also take a function which consumes the x component and uses it in the computation. Just syntactic sugar.. best to wean off of this way of doing things.. but that is one of the nice things about Haskell, you CAN do this sort of thing easily. The definitions: fromto :: forall b a. Enum a => a -> a -> (a -> b) -> [b] fromto a b f = map f [a..b] -- -------------------------------------- fromtoby :: forall a b. (Num a, Enum a) => a -> a -> a -> (a -> b) -> [b] fromtoby a b c f = map f [a,a+c..b] -- ------------------------------------------------------ Some applications using ghci with enhancements turned on... *Iteration> fromto 10 25 id [10,11,12,13,14,15,16,17,18,19,20,21,22,23,24,25] --raw list using id *Iteration> fromto 10 25 (2*) [20,22,24,26,28,30,32,34,36,38,40,42,44,46,48,50] -- list times 2 *Iteration> fromtoby 1 12 2 id -- using id to show what the base list is [1,3,5,7,9,11] *Iteration> fromtoby 1 12 2 (flip (^) 3) -- cubing of the base list above.. [1,27,125,343,729,1331] *Iteration> fromtoby 12 42 3 id [12,15,18,21,24,27,30,33,36,39,42] -- raw list gen'd by id *Iteration> fromtoby 12 42 3 (flip (**) 0.3333333333) [2.2894284849170297, 2.4662120741078493, -- approx. cube roots 2.6207413939563993,2.7589241761011336, 2.884499140309247,2.999999999670416, 3.1072325056015817,3.2075343296219874, 3.3019272485002094,3.391211442600036, 3.4760266444533747] Greetings from the Yuma Desert, gene

On Sat, 19 Aug 2006 10:28:33 +0200, Gene A
*Iteration> fromtoby 1 12 2 (flip (^) 3) -- cubing of the base list above..
An easier way to write this: fromtoby 1 12 2 (^3) [...]
*Iteration> fromtoby 12 42 3 (flip (**) 0.3333333333)
fromtoby 12 42 3 (**0.3333333333)
Greetings from the Yuma Desert, gene _______________________________________________
Greetings from Holland, Henk-Jan van Tuyl -- http://Van.Tuyl.eu/ -- Using Opera's revolutionary e-mail client: https://secure.bmtmicro.com/opera/buy-opera.html?AID=789433

Hi Lennart,
This morning when I posted..it was about 2:30am and had been up a
long time... bad habits.. I sent a message to Henk-Jan to that effect,
but didn't send to the entire list.. anyway thanks to both for the
followups... I still tend to sometimes do things the hard way in
Haskell. Started trying to learn it starting in I think Nov-Dec. of
2005, so not too awfully long, but with a lot of other things soaking
up time, not as far along as I wished to be in even this amount of
time... Most interesting language I have used yet.
but yes not sure why not the precision.. but I think when I tried
that with the way I had the thing in the original, I used (**) 1/3
and got an error message which I was too tired to even read,..and just
changed it to 0.33333333 or whatever .... however many 3's , and just
got it posted.. I don't think that those functions are of much use,
the thing was that when I wrote them, not at 2AM in the morning, I
remember thinking just how easy it was to do pretty much anything you
want with this language.. Off topic, but one of my tests of a
language, old habit this, is as soon as I know enough to be dangerous,
I try writing a forth interpreter in it. I have started such a thing,
a module I call Hforth, and it is operational, but do to the nature of
lists not holding homogeneos values in Haskell everything has to be
stored with String values. This has the result of having to apply
show function to store numerics to the stack and then to use the read
function to convert back when popping the stack.. .. hmm still
tired... Anyway the upshot is that a very rudimentary interpreter is
up and running to do simple things with just builtins so far, but was
built in a matter of some fairly small number of hours. Doesn't
support line editing yet, so really not too good, but does support
pushing strings and concatenation and some other things that are more
tedious to write as primatives in other languages.. The only other
language that was as easy to get to this stage with was scheme.
Sorry for the ramble,
gene
On 8/19/06, Lennart Augustsson
On Aug 19, 2006, at 05:14 , Henk-Jan van Tuyl wrote:
[...]
*Iteration> fromtoby 12 42 3 (flip (**) 0.3333333333)
fromtoby 12 42 3 (**0.3333333333)
And why approximate so much?
fromtoby 12 42 3 (** (1/3))

There are much better ways than storing strings on the stack. Like using a data type with constructors for the different types that you can store. -- Lennart On Aug 19, 2006, at 11:51 , Gene A wrote:
Hi Lennart,
This morning when I posted..it was about 2:30am and had been up a long time... bad habits.. I sent a message to Henk-Jan to that effect, but didn't send to the entire list.. anyway thanks to both for the followups... I still tend to sometimes do things the hard way in Haskell. Started trying to learn it starting in I think Nov-Dec. of 2005, so not too awfully long, but with a lot of other things soaking up time, not as far along as I wished to be in even this amount of time... Most interesting language I have used yet.
but yes not sure why not the precision.. but I think when I tried that with the way I had the thing in the original, I used (**) 1/3 and got an error message which I was too tired to even read,..and just changed it to 0.33333333 or whatever .... however many 3's , and just got it posted.. I don't think that those functions are of much use, the thing was that when I wrote them, not at 2AM in the morning, I remember thinking just how easy it was to do pretty much anything you want with this language.. Off topic, but one of my tests of a language, old habit this, is as soon as I know enough to be dangerous, I try writing a forth interpreter in it. I have started such a thing, a module I call Hforth, and it is operational, but do to the nature of lists not holding homogeneos values in Haskell everything has to be stored with String values. This has the result of having to apply show function to store numerics to the stack and then to use the read function to convert back when popping the stack.. .. hmm still tired... Anyway the upshot is that a very rudimentary interpreter is up and running to do simple things with just builtins so far, but was built in a matter of some fairly small number of hours. Doesn't support line editing yet, so really not too good, but does support pushing strings and concatenation and some other things that are more tedious to write as primatives in other languages.. The only other language that was as easy to get to this stage with was scheme.
Sorry for the ramble, gene
On 8/19/06, Lennart Augustsson
wrote: On Aug 19, 2006, at 05:14 , Henk-Jan van Tuyl wrote:
[...]
*Iteration> fromtoby 12 42 3 (flip (**) 0.3333333333)
fromtoby 12 42 3 (**0.3333333333)
And why approximate so much?
fromtoby 12 42 3 (** (1/3))

Lennart and all,
On 8/19/06, Lennart Augustsson
There are much better ways than storing strings on the stack. Like using a data type with constructors for the different types that you can store.
-- Lennart
Off topic, but .... this is important info for me! Okay then, by doing that you can define a new type that "encodes" the other types.. such that you can actually end up storing the different types such as Int, Integer,Real, String, etc into a list ..... using this new type to so that even though you are in effect storing differing types to a list.. they are actually of the same type and thus legal... without doing an explicit bunch of "read"/"show" combinations.. to actually convert.. .... like Num for example... and being able to use +,* on any of the numeric types... but can you have a list of type [Num] ?? I thought that it had to be the base types of Int, Integer, Float, Double etc.. No? thanks, gene

Hello Gene, Monday, August 21, 2006, 12:42:17 PM, you wrote:
being able to use +,* on any of the numeric types... but can you have a list of type [Num] ?? I thought that it had to be the base types of Int, Integer, Float, Double etc.. No?
you can, using existentials: data Number = forall a. (Num a, Show a) => Num a main = print [Num (1::Int), Num (1.1::Double), Num (1::Integer)] but that is not really very important. in my own practice, homogeneous lists are suffice in almost all cases you can read recent discussion on this in this topic, or look at http://haskell.org/haskellwiki/OOP_vs_type_classes, where John Meacham and me describes how existentials can partially emulate OOP classes -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

On 2006 August 21 Monday 04:42, Gene A wrote:
but can you have a list of type [Num] ?? I thought that it had to be the base types of Int, Integer, Float, Double etc.. No?

I don't know exactly what types you have as base types in your implementation, but here's a small code fragment that of what I had in mind. data Value = D Double | S String | B Bool type Stack = [Value] -- Add top stack elements plus :: Stack -> Stack plus (D x : D y : vs) = D (x+y) : vs plus ( _ : _ : _) = error "Bad operands to plus" plus _ = error "Not enough operands on stack" equal :: Stack -> Stack equal (D x : D y : vs) = B (x == y) : vs equal (S x : S y : vs) = B (x == y) : vs equal (B x : B y : vs) = B (x == y) : vs equal ( _ : _ : _) = error "Bad operands to equal" equal _ = error "Not enough operands on stack" -- Lennart On Aug 21, 2006, at 04:42 , Gene A wrote:
Lennart and all,
On 8/19/06, Lennart Augustsson
wrote: There are much better ways than storing strings on the stack. Like using a data type with constructors for the different types that you can store.
-- Lennart
Off topic, but .... this is important info for me! Okay then, by doing that you can define a new type that "encodes" the other types.. such that you can actually end up storing the different types such as Int, Integer,Real, String, etc into a list ..... using this new type to so that even though you are in effect storing differing types to a list.. they are actually of the same type and thus legal... without doing an explicit bunch of "read"/"show" combinations.. to actually convert.. .... like Num for example... and being able to use +,* on any of the numeric types... but can you have a list of type [Num] ?? I thought that it had to be the base types of Int, Integer, Float, Double etc.. No?
thanks, gene _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Hi All, I got up this morning {after not much sleep} to find these very helpful suggestions/comments: from Scott Turner: {... See: http://www.haskell.org/hawiki/ExistentialTypes ...}
From Bulat Ziganshin: {... you can read recent discussion on this in this topic, or look at http://haskell.org/haskellwiki/OOP_vs_type_classes ....}
From Lennart Augustsson, A wonderfully instructive code fragment: {... data Value = D Double | S String | B Bool type Stack = [Value] -- Add top stack elements plus :: Stack -> Stack plus (D x : D y : vs) = D (x+y) : vs plus ( _ : _ : _) = error "Bad operands to plus" plus _ = error "Not enough operands on stack" ...} see his post for the continuation...
With these suggestions I have plenty to study now.. and probably a whole redesign of some of the things that I have already implemented.. with most likely a great boost in speed of execution, and much cleaner code. I must admit that some of these concepts have not come as easily to me as to some that have had formal education in these matters... This list and the materials from Haskell.org, papers on various websites, and documentation with GHC and it's libraries are my entire exposure.. so when stuck, kind folks from the net community are my, I guess mentors would be the word I am looking for... and for that I am very greatful! I am not in a real race... but I have to thank everyone that participated in this spawned off of the main topic discussion... for all their patience with my questions.. Thanks again to All for the clarification and links to more reading, gene
participants (11)
-
ajb@spamcop.net
-
Antti-Juhani Kaijanaho
-
Bulat Ziganshin
-
Chris Kuklewicz
-
Christian Maeder
-
Gene A
-
Henk-Jan van Tuyl
-
ivan gomez rodriguez
-
Lennart Augustsson
-
Scott Turner
-
Tamas K Papp