[Haskell-cafe] turning an imperative loop to Haskell
Axel Gerstenberger
axel.gerstenberger at gmx.de
Thu Sep 6 10:06:45 EDT 2007
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 <axel.gerstenberger at gmx.de> 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.
>
More information about the Haskell-Cafe
mailing list