turning an imperative loop to Haskell

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 20000 $ 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

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 20000 $ 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.htm...) See also: http://www.haskell.org/haskellwiki/Things_to_avoid#Lists_are_not_arrays

On 06/09/07, Axel Gerstenberger
module Main where
import System.IO import Text.Printf
main :: IO () main = do let all_results1 = take 20000 $ 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.

Dougal Stanton wrote:
To create an infinite list where each f(u) depends on the previous u, with a single seed value, use 'iterate':
main = mapM_ (uncurry (printf "%d %f\n")) (zip [1..50] (iterate f 3))
How about main = sequence_ $ zipWith (printf "%d %f\n") [1..50] (iterate f 3) Regards, apfelmus

On Thu, Sep 06, 2007 at 03:42:50PM +0200, apfelmus wrote:
Dougal Stanton wrote:
To create an infinite list where each f(u) depends on the previous u, with a single seed value, use 'iterate':
main = mapM_ (uncurry (printf "%d %f\n")) (zip [1..50] (iterate f 3))
How about
main = sequence_ $ zipWith (printf "%d %f\n") [1..50] (iterate f 3)
Better yet: main = zipWithM_ (printf "%d %f\n") [1..50] (iterate f 3) Stefan

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
wrote: module Main where
import System.IO import Text.Printf
main :: IO () main = do let all_results1 = take 20000 $ 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.

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

On 06/09/07, 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)), ...]
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

On 06/09/07, Sebastian Sylvan
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.

On 9/6/07, Dougal Stanton
On 06/09/07, Sebastian Sylvan
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/A000073 All of which are a form of Tribonacci numbers. -- Dan

On 06/09/07, Axel Gerstenberger
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

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
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
wrote: module Main where
import System.IO import Text.Printf
main :: IO () main = do let all_results1 = take 20000 $ 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

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

Hi all, thanks again for all the responses on the "imperative loop" question. Here is another questions: I am used to work with map, zip and zipWith, when working with lists, however, I could not find such functions for Arrays. For example, in my Finite Element prototype, I have a function
type Dof = Double type TimeInc = Double
predictU :: Double -> TimeInc -> Dof -> Dof -> Dof -> Dof predictU beta dt u u_t u_tt = u + dt*u_t + ((dt**2.0)/2.0)*(1.0 - 2.0*beta ) * u_tt
Given 3 equal sized lists un, vn and an of double values [Dof], I apply it with
u_est = zipWith3 (predictU beta dt) un vn an
I like it's conciseness, but is that efficient? The lists can be very long and correspond to a plain C++ vectors in corresponding C++ codes. my own "map" for a vector I defined based on the Array documention (Data.Array) as
mapVec f vec = vec//[ (i, f(vec!i)) |i<-[a..b]] where (a,b) = bounds vec
I guess, I could implement zip and zipWith in a similar manner, but using list comprehension seems weird and inefficient here. I wonder if these standard functions are already defined somewhere. I only found "amap" for IArrays http://cvs.haskell.org/Hugs/pages/libraries/base/Data-Array-IArray.html but no zip, zipWith or even zipWith3. The whole point of using (unboxed) Arrays instead of lists is memory performce and speead of random access. Any hints on how to do zipWith on arrays is highly appreciated. Best, Axel Gerstenberger Henning Thielemann schrieb:
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

On Sun, 9 Sep 2007, Axel Gerstenberger wrote:
I am used to work with map, zip and zipWith, when working with lists, however, I could not find such functions for Arrays.
Since 'Array' is an instance of Functor you can use 'fmap' for applying a function to all elements.
For example, in my Finite Element prototype, I have a function
type Dof = Double type TimeInc = Double
predictU :: Double -> TimeInc -> Dof -> Dof -> Dof -> Dof predictU beta dt u u_t u_tt = u + dt*u_t + ((dt**2.0)/2.0)*(1.0 - 2.0*beta ) * u_tt
Given 3 equal sized lists un, vn and an of double values [Dof], I apply it with
u_est = zipWith3 (predictU beta dt) un vn an
I like it's conciseness, but is that efficient?
The problem with combining array is, that they can not only differ in length, but can also have different start indices. How to handle this generically? The best way to express that two vectors have the same interval of indices is to put them in one array, e.g. Array i (a, b) instead of (Array i a, Array i b) Of course this is not alway possible.
The lists can be very long and correspond to a plain C++ vectors in corresponding C++ codes.
Lists can still be the better structure for your application if you do not need random access.
my own "map" for a vector I defined based on the Array documention (Data.Array) as
mapVec f vec = vec//[ (i, f(vec!i)) |i<-[a..b]] where (a,b) = bounds vec
You do not need update (//) if you overwrite all elements. (//) generates a new array anyway. Btw. you can obtain all indices of an array by range (bounds vec)

On 9 Sep 2007, at 10:05 pm, Axel Gerstenberger wrote:
I am used to work with map, zip and zipWith, when working with lists, however, I could not find such functions for Arrays.
They aren't there for at least two reasons. (1) They are easy to implement on top of the operations that are provided. (EASY is not the same as EFFICIENT, of course.) (2) In some cases it isn't obvious what the operations should be. I note as a counter-argument that Clean provides, in addition to list comprehension and list generators, array comprehension and array generators, so maps and zips of any arity are directly and transparently available in a very Haskell-like language. I note as a counter-counter-argument that Clean is free of Haskell's "Ix" baggage, which takes us back to (2). zip being a special case of zipWith, let's consider just map and zipWith. amap :: Ix i => (a -> b) -> Array i a -> Array i b amap f arr = listArray (bounds arr) (map f (elems arr)) A more general version of this is available, under that name, in Data.Array.IArray, and Data.Array.MArray gives you mapArray. aZipWith :: Ix i => (a -> b -> c) -> Array i a -> Array i b -> Array i c aZipWith f a1 a2 = if bounds a1 == bounds a2 then listArray (bounds a1) (zipWith f (elems a1) (elems a2)) else error "aZipWith: array bounds do not agree" But do you really want aMap's result to have the same bounds as its argument? If not, what bounds do you want it to have? Do you want aZipWith to fail if the arrays haven't exactly the same bounds, or do you want to work with the intersection of their bounds, or what? A worse problem these days is that in the dotted libraries there are so *many* variants of arrays. We need to start writing stuff like aZipWith :: (Ix i, IArray a1 e1, IArray a2 e2, IArray a3 e3) => (e1 -> e2 -> e3) -> a1 i a1 -> a2 i e2 -> a3 i e3 and this is deeper waters than I am comfortable swimming in. (What's the best thing to read to explain functional dependencies for multi-parameter type classes?)

Hello ok, Monday, September 10, 2007, 7:03:34 AM, you wrote:
(What's the best thing to read to explain functional dependencies for multi-parameter type classes?)
ghc 6.6+ docs. but 1) arrays don't use FDs 2) FDs are old technique. starting with ghc 6.8, ATs will be available and should be used instead: http://haskell.org/haskellwiki/GHC/Type_families -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

ok wrote:
On 9 Sep 2007, at 10:05 pm, Axel Gerstenberger wrote:
I am used to work with map, zip and zipWith, when working with lists, however, I could not find such functions for Arrays.
They aren't there for at least two reasons. (1) They are easy to implement on top of the operations that are provided. (EASY is not the same as EFFICIENT, of course.) (2) In some cases it isn't obvious what the operations should be.
I note as a counter-argument that Clean provides, in addition to list comprehension and list generators, array comprehension and array generators, so maps and zips of any arity are directly and transparently available in a very Haskell-like language.
I note as a counter-counter-argument that Clean is free of Haskell's "Ix" baggage, which takes us back to (2).
LOL! Now there's a convuloted argument... Personally, I always use 0-origin arrays. I often forget that it's *possible* to use something else. (The obvious example being tuple indexes...)
zip being a special case of zipWith, let's consider just map and zipWith.
I also find it puzzling that the mutable arrays do not provide an analogue of map with works in-place. (Surely this is the entire *point* of mutable arrays?) I mean, it's not difficult to implement it manually yourself, but we all know that home-grown implementations aren't ideal.
But do you really want aMap's result to have the same bounds as its argument? If not, what bounds do you want it to have? Do you want aZipWith to fail if the arrays haven't exactly the same bounds, or do you want to work with the intersection of their bounds, or what?
How about you specify what bounds you want in the zip call? And it then iterates the two arrays from beginning to end like the normal list-zip does. (Of course, then it has a different arity in addition to a different type signature...)
A worse problem these days is that in the dotted libraries there are so *many* variants of arrays. We need to start writing stuff like
aZipWith :: (Ix i, IArray a1 e1, IArray a2 e2, IArray a3 e3) => (e1 -> e2 -> e3) -> a1 i a1 -> a2 i e2 -> a3 i e3
and this is deeper waters than I am comfortable swimming in.
Yeah, I get the impression that the entire thing wants redesigning. It's too complicated and ad-hoc at the moment. (OTOH, who is going to undertake this?)
(What's the best thing to read to explain functional dependencies for multi-parameter type classes?)
Good question...
participants (12)
-
Andrew Coppin
-
apfelmus
-
Axel Gerstenberger
-
Bulat Ziganshin
-
Dan Piponi
-
Dougal Stanton
-
Henning Thielemann
-
Jules Bean
-
ok
-
Rodrigo Queiro
-
Sebastian Sylvan
-
Stefan O'Rear