
To: haskell-cafe@haskell.org From: to.darkangel@gmail.com Date: Tue, 19 Mar 2013 23:27:09 +0200 Subject: Re: [Haskell-cafe] Streaming bytes and performance
On 03/19/2013 10:49 PM, Konstantin Litvinenko wrote:
{-# LANGUAGE BangPatterns #-}
import Control.Monad.State.Strict
data S6 = S6 !Int !Int
main_6 = do let r = evalState go (S6 10000 0) print r where go = do (S6 i a) <- get if (i == 0) then return a else (put (S6 (i - 1) (a + i))) >> go
main_7 = do let r = go (S6 10000 0) print r where go (S6 i a) | i == 0 = a | otherwise = go $ S6 (i - 1) (a + i)
main = main_6
main_6 doing constant allocations while main_7 run in constant space. Can you suggest something that improve situation? I don't want to manually unfold all my code that I want to be fast :(. Your problem is that main_6 thunks 'i' and 'a' .If you write (S6 !i !a) <- getthan there is no problem any more...
Correction - they both run in constant space, that's not a problem. The problem is main_6 doing constant allocation/destroying and main_7 doesn't. No main_6 does not runs in constant space if you dont use bang patterns...