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

Daniel Fischer daniel.is.fischer at web.de
Sat Oct 10 17:11:24 EDT 2009


Am Samstag 10 Oktober 2009 22:14:38 schrieb mf-hcafe-15c311f0c at etc-network.de:
> On Sat, Oct 10, 2009 at 09:33:52AM -0700, Thomas Hartman wrote:
> > To: Luke Palmer <lrpalmer at gmail.com>
> > Cc: mf-hcafe-15c311f0c at etc-network.de, haskell-cafe at haskell.org
> > From: Thomas Hartman <tphyahoo at gmail.com>
> > Date: Sat, 10 Oct 2009 09:33:52 -0700
> > Subject: Re: [Haskell-cafe] How do I get this done in constant mem?
> >
> > > Yes, you should not do this in IO.  That requires the entire
> > > computation to finish before the result can be used.
> >
> > Not really the entire computation though... whnf, no?
>
> In that example, yes.  But readFile takes the entire file into a
> strict String before it gives you the first Char, right?  (Sorry again
> for my misleading code "simplification".)

No, readFile reads the file lazily.

>
> > main = do
> >   let thunks :: IO [Int]
> >   thunks = (sequence . replicate (10^6) $ (randomRIO (0,10^9)))
> >   putStrLn . show . head =<< thunks -- prints
> >   putStrLn . show . last =<< thunks -- overflows
>
> Meaning that the entire list needs to be kept?  Is there a reason
> (other than "it's easier to implement and it's legal" :-) why the
> elements that have been traversed by "last" can't be garbage
> collected?
>

The problem is that the randomRIO isn't done before it's needed. When you ask for the last 
element of the generated list, you have a stack of nearly one million calls to randomRIO 
to get it, that overflows the stack.
If you insert a stricter version of sequence:

{-# LANGUAGE BangPatterns #-}

sequence'       :: Monad m => [m a] -> m [a]
{-# INLINE sequence' #-}
sequence' ms = foldr k (return []) ms
            where
              k m m' = do { !x <- m; xs <- m'; return (x:xs) }
--                     ^^^^^^^^^^^ evaluate x now!

main = do
    let thunks = sequence' . replicate (10^6) $ randomRIO (0,10^9)
...

it doesn't overflow the stack. But both, sequence and sequence' must construct the entire 
list, so they use quite a bit of memory.
You can keep the memory usage low by using unsafeInterleaveIO.

>
>
> -m




More information about the Haskell-Cafe mailing list