Fwd: [Haskell-cafe] turning an imperative loop to Haskell

2007-09-07 Thread Stephen Dolan
Sorry, forgot to cc list I think this is called taking a good thing too far, but cool too: f1 u = u + 1 f2 u v = u + v f3 u v w = u + v + w -- functions renamed for consistency) zipWith1 = map zipWith2 = zipWith -- and hey presto! us1 = 3 : zipWith1 f1 us1 us2 = 2 : 3 : zipWith2 f2

[Haskell-cafe] turning an imperative loop to Haskell

2007-09-06 Thread Axel Gerstenberger
Hi all, I am completely stuck with a problem involving a loop construct from imperative programming, that I want to translate to Haskell code. The problem goes as follows: Based on a value u_n, I can calculate a new value u_{n+1} with a function f(u). u_n was calculated from u_{n-1} and so on

Re: [Haskell-cafe] turning an imperative loop to Haskell

2007-09-06 Thread Henning Thielemann
On Thu, 6 Sep 2007, Axel Gerstenberger wrote: module Main where import System.IO import Text.Printf main :: IO () main = do let all_results1 = take 2 $ step [1] --print $ length all_results1 -- BTW: if not commented out, -- all values of

Re: [Haskell-cafe] turning an imperative loop to Haskell

2007-09-06 Thread Dougal Stanton
On 06/09/07, Axel Gerstenberger [EMAIL PROTECTED] wrote: module Main where import System.IO import Text.Printf main :: IO () main = do let all_results1 = take 2 $ step [1] --print $ length all_results1 -- BTW: if not commented out, --

Re: [Haskell-cafe] turning an imperative loop to Haskell

2007-09-06 Thread Axel Gerstenberger
Thanks to all of you. The suggestions work like a charm. Very nice. I still need to digest the advices, but have already one further question: How would I compute the new value based on the 2 (or even more) last values instead of only the last one? [ 2, 3 , f 3 2, f((f 3 2) 3), f ( f((f 3 2)

Re: [Haskell-cafe] turning an imperative loop to Haskell

2007-09-06 Thread Jules Bean
Axel Gerstenberger wrote: Thanks to all of you. The suggestions work like a charm. Very nice. I still need to digest the advices, but have already one further question: How would I compute the new value based on the 2 (or even more) last values instead of only the last one? [ 2, 3 , f 3 2,

Re: [Haskell-cafe] turning an imperative loop to Haskell

2007-09-06 Thread Sebastian Sylvan
On 06/09/07, Axel Gerstenberger [EMAIL PROTECTED] wrote: Thanks to all of you. The suggestions work like a charm. Very nice. I still need to digest the advices, but have already one further question: How would I compute the new value based on the 2 (or even more) last values instead of only

Re: [Haskell-cafe] turning an imperative loop to Haskell

2007-09-06 Thread Dougal Stanton
On 06/09/07, Axel Gerstenberger [EMAIL PROTECTED] wrote: however,I don't get it this to work. Is it possible to see the definition of the iterate function? The online help just shows it's usage... The Haskell 98 report includes source for the standard prelude. Check 'em out...

Re: [Haskell-cafe] turning an imperative loop to Haskell

2007-09-06 Thread Rodrigo Queiro
When you get to more than two arguments, it will probably be nicer to do something like this: fibs = map (\(a,b) - a) $ iterate (\(a,b) - (b, a+b)) (0,1) or fibs = unfoldr (\(a,b) - Just (a, (b, a+b))) (0,1) -- this uses unfoldr to get rid of the map This is essentially a translation of the

Re: [Haskell-cafe] turning an imperative loop to Haskell

2007-09-06 Thread Dougal Stanton
On 06/09/07, Sebastian Sylvan [EMAIL PROTECTED] wrote: foo = 2 : 3 : zipWith f (drop 1 foo) foo There's also zipWith3 etc. for functions with more arguments. I think this is called taking a good thing too far, but cool too: f1 u = u + 1 f2 u v = u + v f3 u v w = u + v + w -- functions

Re: [Haskell-cafe] turning an imperative loop to Haskell

2007-09-06 Thread Henning Thielemann
On Thu, 6 Sep 2007, Axel Gerstenberger wrote: Thanks to all of you. The suggestions work like a charm. Very nice. I still need to digest the advices, but have already one further question: How would I compute the new value based on the 2 (or even more) last values instead of only the last

Re: [Haskell-cafe] turning an imperative loop to Haskell

2007-09-06 Thread Dan Piponi
On 9/6/07, Dougal Stanton [EMAIL PROTECTED] wrote: On 06/09/07, Sebastian Sylvan [EMAIL PROTECTED] wrote: [2,3,4,9,16,29,54,99,182,335] -- what's this? Two times this: http://www.research.att.com/~njas/sequences/A000213 plus this: http://www.research.att.com/~njas/sequences/A001590 plus two