[Haskell-cafe] turning an imperative loop to Haskell

Axel Gerstenberger axel.gerstenberger at gmx.de
Thu Sep 6 08:14:27 EDT 2007


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




More information about the Haskell-Cafe mailing list