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 (drop 1 us2) us2
 us3 = 2 : 3 : 4 : zipWith3 f3 (drop 2 us3) (drop 1 us3) us3

How about this:
import Data.List -- for transpose
f  = sum
zipWithN fn = map fn . transpose
us k = s
  where
  s = [2..k+1] ++ (zipWithN f $ x $ map (flip drop s) [0..k-1])

take 10 (us 1)
[2,2,2,2,2,2,2,2,2,2]
take 10 (us 2)
[2,3,5,8,13,21,34,55,89,144]
take 10 (us 3)
[2,3,4,9,16,29,54,99,182,335]
take 10 (us 4)
[2,3,4,5,14,26,49,94,183,352]

We can always take it further :D
Stephen
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[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 down to some
initial value u_0. So far it looks like a standard recursion to me.

The main goal is to write each result u_{n+1} to a file or screen.

The problem arises (for me), when u is an array of doubles or a complex
data object instead of a simple Double/Integer value, so that I can
store only maybe the last or the two last steps in memory. I never need
older values. In C, I would write a for loop, calculate the new u and
write it to the file. Then I update the old values to the new ones and
do the next step in the for loop.

Here is what I did in Haskell: I create an infinite list and tried to
print the n-th value to the screen/file. But it always calculates all
values in the list all_results, before it starts printing values to
screen. On the other side, the function f is called exactly 50 times as
the loop suggests. The result is correct, however, it would prohibitive
much memory for more complex data and more steps.

Can anyone help in explaining me, how I can print to screen and still
keep only the last needed values in memory? I can only find imperative
solutions, but maybe it is an imperative problem anyway.?

Thanks for your time.

Best Axel

My approach:


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 all_results
  --  are already
  --  calculated here
loop [1..50] $ \i - do
let x = all_results1!!i
putStrLn $ show i ++++ show x

-- create an infinite list with values u_{n+1} ++ [u_n,u_{n-1},...,u_1]
-- where u_{n+1} = f (u_n)
step history =
case history of
[]   - error no start values
xs   - xs ++ (step [ f (head $ reverse (xs) )])

f u = u + 1 + (sqrt u) -- some arbitrary complex function


-- copied from some blog, not sure if this is a good way
loop ns stuff = mapM_ stuff ns


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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 all_results
 --  are already
 --  calculated here
   loop [1..50] $ \i - do
   let x = all_results1!!i
   putStrLn $ show i ++++ show x


The guilty thing is (!!). Better write

loop all_results1 $ \x - do
  putStrLn $ show i ++++ show x

In your program, the reference to the beginning of the list all_results1 
is kept throughout the loop and thus the garbage collector cannot free the 
memory.


('loop' is available as 'forM_' in GHC-6.6
   
http://www.haskell.org/ghc/docs/latest/html/libraries/base/Control-Monad.html#v%3AforM_)


See also:
 http://www.haskell.org/haskellwiki/Things_to_avoid#Lists_are_not_arrays
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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,
--  all values of all_results
--  are already
--  calculated here
  loop [1..50] $ \i - do
  let x = all_results1!!i
  putStrLn $ show i ++++ show x

 -- create an infinite list with values u_{n+1} ++ [u_n,u_{n-1},...,u_1]
 -- where u_{n+1} = f (u_n)
 step history =
  case history of
  []   - error no start values
  xs   - xs ++ (step [ f (head $ reverse (xs) )])

To create an infinite list where each f(u) depends on the previous u,
with a single seed value, use 'iterate':

Prelude let us = iterate f 3

That produces your infinite list of values, starting with [f 3, f(f3),
f(f(f 3)), ...]. Pretty neat.

Then all you really need is

main = mapM_ (uncurry (printf %d %f\n)) (zip [1..50] (iterate f 3))

You can probably shorten this a bit more with arrows but I've got a
cold at the moment and not really thinking straight.

Cheers,

D.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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) 3)  f 3 2)), ...]

(background: I am doing explicit time stepping for some physical 
problem, where higher order time integration schemes are interesting. 
You advance in time by extrapolating based on the old time step values.)


I guess I just wrote the definition and define iterate2 as

iterate2 history =
 case history of
 []   - error no start values
 x1:x2:xs   - iterate2 ([f x1 x2] ++ xs)
or

iterate2 :: [Double] - [Double]
iterate2 history =
 case history of
 []   - error two start values needed
 x1:[]   - error one more start values
 x1:x2:xs   - iterate2 (history ++ ([f a b]))
where [a,b] = take 2 $ reverse history

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...


Again thanks a lot for your ideas and the links. I knew there was a 
one-liner for my problem, but I couldn't find it for days.


Axel

Dougal Stanton wrote:

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,
   --  all values of all_results
   --  are already
   --  calculated here
 loop [1..50] $ \i - do
 let x = all_results1!!i
 putStrLn $ show i ++++ show x

-- create an infinite list with values u_{n+1} ++ [u_n,u_{n-1},...,u_1]
-- where u_{n+1} = f (u_n)
step history =
 case history of
 []   - error no start values
 xs   - xs ++ (step [ f (head $ reverse (xs) )])


To create an infinite list where each f(u) depends on the previous u,
with a single seed value, use 'iterate':

Prelude let us = iterate f 3

That produces your infinite list of values, starting with [f 3, f(f3),
f(f(f 3)), ...]. Pretty neat.

Then all you really need is

main = mapM_ (uncurry (printf %d %f\n)) (zip [1..50] (iterate f 3))

You can probably shorten this a bit more with arrows but I've got a
cold at the moment and not really thinking straight.

Cheers,

D.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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, f((f 3 2) 3), f ( f((f 3 2) 3)  f 3 2)), ...]



You define the whole list recursively. This is commonly shown as an 
example for the fibonacci numbers; yours is similar:


axelg = 2 : 3 : zipWith f (tail axelg) axelg

...indeed, in the case where f = (+) this *is* the fibonacci sequence:

Prelude let axelg = 2 : 3 : zipWith (+) (tail axelg) axelg in take 10 axelg
[2,3,5,8,13,21,34,55,89,144]

Jules

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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 the last one?

 [ 2, 3 , f 3 2, f((f 3 2) 3), f ( f((f 3 2) 3)  f 3 2)), ...]

foo = 2 : 3 : zipWith f (drop 1 foo) foo

There's also zipWith3 etc. for functions with more arguments.

-- 
Sebastian Sylvan
+44(0)7857-300802
UIN: 44640862
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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...

http://www.haskell.org/onlinereport/standard-prelude.html



 Again thanks a lot for your ideas and the links. I knew there was a
 one-liner for my problem, but I couldn't find it for days.

That's a common feeling with Haskell, I think. ;-)

D
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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 imperative algorithm - the
state is stored in the tuple, which is repeatedly transformed by the
function \(a,b) - (b, a+b), and then you extract the values to be
yielded from the state with \(a,b) - a.

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 the last one?

 [ 2, 3 , f 3 2, f((f 3 2) 3), f ( f((f 3 2) 3)  f 3 2)), ...]

 (background: I am doing explicit time stepping for some physical
 problem, where higher order time integration schemes are interesting.
 You advance in time by extrapolating based on the old time step values.)

 I guess I just wrote the definition and define iterate2 as

 iterate2 history =
   case history of
   []   - error no start values
   x1:x2:xs   - iterate2 ([f x1 x2] ++ xs)
 or

 iterate2 :: [Double] - [Double]
 iterate2 history =
   case history of
   []   - error two start values needed
   x1:[]   - error one more start values
   x1:x2:xs   - iterate2 (history ++ ([f a b]))
  where [a,b] = take 2 $ reverse history

 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...

 Again thanks a lot for your ideas and the links. I knew there was a
 one-liner for my problem, but I couldn't find it for days.

 Axel

 Dougal Stanton wrote:
  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,
 --  all values of all_results
 --  are already
 --  calculated here
   loop [1..50] $ \i - do
   let x = all_results1!!i
   putStrLn $ show i ++++ show x
 
  -- create an infinite list with values u_{n+1} ++ [u_n,u_{n-1},...,u_1]
  -- where u_{n+1} = f (u_n)
  step history =
   case history of
   []   - error no start values
   xs   - xs ++ (step [ f (head $ reverse (xs) )])
 
  To create an infinite list where each f(u) depends on the previous u,
  with a single seed value, use 'iterate':
 
  Prelude let us = iterate f 3
 
  That produces your infinite list of values, starting with [f 3, f(f3),
  f(f(f 3)), ...]. Pretty neat.
 
  Then all you really need is
 
  main = mapM_ (uncurry (printf %d %f\n)) (zip [1..50] (iterate f 3))
 
  You can probably shorten this a bit more with arrows but I've got a
  cold at the moment and not really thinking straight.
 
  Cheers,
 
  D.
 
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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 renamed for consistency)
zipWith1 = map
zipWith2 = zipWith

-- and hey presto!
us1 = 3 : zipWith1 f1 us1
us2 = 2 : 3 : zipWith2 f2 (drop 1 us2) us2
us3 = 2 : 3 : 4 : zipWith3 f3 (drop 2 us3) (drop 1 us3) us3

*Main take 10 us1
[3,4,5,6,7,8,9,10,11,12] -- integers from three upwards
*Main take 10 us2
[2,3,5,8,13,21,34,55,89,144] -- fibonacci
*Main take 10 us3
[2,3,4,9,16,29,54,99,182,335] -- what's this?

Cheers,

D.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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 one?


[ 2, 3 , f 3 2, f((f 3 2) 3), f ( f((f 3 2) 3)  f 3 2)), ...]

(background: I am doing explicit time stepping for some physical problem, 
where higher order time integration schemes are interesting. You advance in 
time by extrapolating based on the old time step values.)


You might be interested in some ideas on how to solve differential 
equations numerically in an elegant way:

 http://darcs.haskell.org/htam/src/Numerics/ODEEuler.lhs
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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 times this: http://www.research.att.com/~njas/sequences/A73

All of which are a form of Tribonacci numbers.
--
Dan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe