How to implement nested loops with tail recursion?

I need to implement fast two-level loops, and I am learning using seq to make calls tail-recursive.
I write programs to compute
main = print $ sum [i*j|i::Int<-[1..20000],j::Int<-[1..20000]]
This program (compiled with -O2) runs twenty times slower than the unoptimized (otherwise the loop gets optimized out) C version.
But it seems to run in constant memory, so I assume that it has been turned into loops.
#include

Now I have discovered the right version...
main = print (f 1 0::Int) where
f i s = (if i<=20000 then (f (i+1) (s + g 1 0)) else s) where
g j s = (if j<=20000 then (g (j+1) (s + i*j)) else s)
----- 原始邮件 -----
发件人: sdiyazg@sjtu.edu.cn
收件人: haskell-cafe@haskell.org
发送时间: 星期三, 2012年 9 月 19日 下午 11:35:11
主题: How to implement nested loops with tail recursion?
I need to implement fast two-level loops, and I am learning using seq to make calls tail-recursive.
I write programs to compute
main = print $ sum [i*j|i::Int<-[1..20000],j::Int<-[1..20000]]
This program (compiled with -O2) runs twenty times slower than the unoptimized (otherwise the loop gets optimized out) C version.
But it seems to run in constant memory, so I assume that it has been turned into loops.
#include

A follow-up question.
I still haven't got the monadic version working, and the real use case involves IO actions.
I looked at http://www.haskell.org/haskellwiki/Recursion_in_a_monad and adapted the 'tail-recursive' snippet on the page into
main = do
let
f 0 acc = return acc
f n acc = do
v <- return 1
f (n-1) (v+acc)
f 1000000 100 >>= print
which still blows the memory.
And so does this program
main = do
s<-newIORef (0::Int)
mapM_ (\i->modifyIORef s (+1)) [0..10000000]
readIORef s>>=print
Why?
----- 原始邮件 -----
发件人: sdiyazg@sjtu.edu.cn
收件人: haskell-cafe@haskell.org
发送时间: 星期四, 2012年 9 月 20日 上午 12:08:19
主题: Re: How to implement nested loops with tail recursion?
Now I have discovered the right version...
main = print (f 1 0::Int) where
f i s = (if i<=20000 then (f (i+1) (s + g 1 0)) else s) where
g j s = (if j<=20000 then (g (j+1) (s + i*j)) else s)
----- 原始邮件 -----
发件人: sdiyazg@sjtu.edu.cn
收件人: haskell-cafe@haskell.org
发送时间: 星期三, 2012年 9 月 19日 下午 11:35:11
主题: How to implement nested loops with tail recursion?
I need to implement fast two-level loops, and I am learning using seq to make calls tail-recursive.
I write programs to compute
main = print $ sum [i*j|i::Int<-[1..20000],j::Int<-[1..20000]]
This program (compiled with -O2) runs twenty times slower than the unoptimized (otherwise the loop gets optimized out) C version.
But it seems to run in constant memory, so I assume that it has been turned into loops.
#include

On Wed, Sep 19, 2012 at 7:24 PM,
main = do let f 0 acc = return acc f n acc = do v <- return 1 f (n-1) (v+acc) f 1000000 100 >>= print
Try this main = do let f :: Int -> Int -> IO Int f 0 !acc = return acc -- note strict accumulator f n acc = do v <- return 1 f (n-1) (v+acc) f 1000000 100 >>= print

So how do I force IO actions whose results are discarded (including IO ()) to be strict?
main = do
s<-newIORef (1::Int)
let
f :: Int -> Int -> IO Int
f 0 !acc = return acc -- note strict accumulator
f n !acc = do
v <- modifyIORef s (+2) >>readIORef s -- reading immediately after writing
f (n-1) (v+acc)
f 1000000 100 >>= print
readIORef s>>=print
runs OK, while
main = do
s<-newIORef (1::Int)
let
f :: Int -> Int -> IO Int
f 0 !acc = return acc -- note strict accumulator
f n !acc = do
v <- modifyIORef s (+2) >>return 1
f (n-1) (v+acc)
f 1000000 100 >>= print
readIORef s>>=print
,
main = do
s<-newIORef (1::Int)
let
f :: Int -> Int -> IO Int
f 0 !acc = return acc -- note strict accumulator
f n !acc = do
v <- modifyIORef s (+2) >>readIORef s>>return 1
f (n-1) (v+acc)
f 1000000 100 >>= print
readIORef s>>=print
and
main = do
s<-newIORef (1::Int)
let
f :: Int -> Int -> IO Int
f 0 !acc = return acc -- note strict accumulator
f n !acc = do
v <- (>>return 1) $! (modifyIORef s (+2) >>readIORef s)
f (n-1) (v+acc)
f 1000000 100 >>= print
readIORef s>>=print
all overflows after correctly printing the first number
----- 原始邮件 -----
发件人: "Johan Tibell"
main = do let f 0 acc = return acc f n acc = do v <- return 1 f (n-1) (v+acc) f 1000000 100 >>= print
Try this main = do let f :: Int -> Int -> IO Int f 0 !acc = return acc -- note strict accumulator f n acc = do v <- return 1 f (n-1) (v+acc) f 1000000 100 >>= print

Hi! On 19/09/12 19:00, sdiyazg@sjtu.edu.cn wrote:
So how do I force IO actions whose results are discarded (including IO ()) to be strict?
() <- foo :: IO () -- should work as it pattern matches, can wrap it in a prettier combinator !_ <- foo :: IO a -- could work with -XBangPatterns I've not tested either (been away from Haskell for a while..), but see also: http://markmail.org/message/i7eufihlhgq4jqt6 (regarding modifyIORef and leaky issues) Claude -- http://mathr.co.uk

On Wed, Sep 19, 2012 at 8:00 PM,
So how do I force IO actions whose results are discarded (including IO ()) to be strict?
In your particular case it looks like you want Data.IORef.modifyIORef'. If your version of GHC doesn't include it you can write it like so: -- |Strict version of 'modifyIORef' modifyIORef' :: IORef a -> (a -> a) -> IO () modifyIORef' ref f = do x <- readIORef ref let x' = f x x' `seq` writeIORef ref x' -- Johan
participants (3)
-
Claude Heiland-Allen
-
Johan Tibell
-
sdiyazg@sjtu.edu.cn