[Haskell-cafe] How do I get this done in constant mem?

Thomas Hartman tphyahoo at gmail.com
Sat Oct 10 11:10:12 EDT 2009


I don't know if this counts but how about

import Control.Applicative
import Control.Monad
import Random
import Data.List

main'' i j = replicateM j $ maximum' <$> (replicateM i . randomRIO $ (0,10^9))
maximum' = foldl1' max
t = main'' (10^4) 5


2009/10/9  <mf-hcafe-15c311f0c at etc-network.de>:
>
>
> Hi all,
>
> I think there is something about my use of the IO monad that bites me,
> but I am bored of staring at the code, so here you g.  The code goes
> through a list of records and collects the maximum in each record
> position.
>
>
> -- test.hs
> import Random
> import System.Environment (getArgs)
> import System.IO (putStr)
>
> samples :: Int -> Int -> IO [[Double]]
> samples i j = sequence . replicate i . sequence . replicate j $ randomRIO (0, 1000 ** 3)
>
> maxima :: [[Double]] -> [Double]
> maxima samples@(_:_) = foldr (\ x y -> map (uncurry max) $ zip x y) (head samples) (tail samples)
>
> main = do
>  args <- getArgs
>  x <- samples (read (head args)) 5
>  putStr . (++ "\n") . show $ maxima x
>
>
> I would expect this to take constant memory (foldr as well as foldl),
> but this is what happens:
>
>
> $ ghc -prof --make -O9 -o test test.hs
> [1 of 1] Compiling Main             ( test.hs, test.o )
> Linking test ...
> $ ./test 100 +RTS -p
> [9.881155955344708e8,9.910336352165401e8,9.71000686630374e8,9.968532576451201e8,9.996200333115692e8]
> $ grep 'total alloc' test.prof
>        total alloc =     744,180 bytes  (excludes profiling overheads)
> $ ./test 10000 +RTS -p
> [9.996199711457872e8,9.998928358545277e8,9.99960283632381e8,9.999707142123885e8,9.998952151508758e8]
> $ grep 'total alloc' test.prof
>        total alloc =  64,777,692 bytes  (excludes profiling overheads)
> $ ./test 1000000 +RTS -p
> Stack space overflow: current size 8388608 bytes.
> Use `+RTS -Ksize' to increase it.
> $
>
>
> so...
>
> does sequence somehow force the entire list of monads into evaluation
> before the head of the result list can be used?  what can i do to
> implement this in constant memory?
>
> thanks!
> matthias
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>


More information about the Haskell-Cafe mailing list