[Haskell-cafe] Why doesn't this consume all the computer's memory?

Viktor Dukhovni ietf-dane at dukhovni.org
Thu Nov 8 19:15:36 UTC 2018


It seems that it only runs in constant space when the two lengths
compile to a pre-evaluated CAF.

In the below version, at low optimization levels the evaluation of lx/ly
is deferred to the "forkIO" thread, and memory use grows linearly with
the timeout.

At high optimization levels, memory use is constant, but the timeout
never happens, and it seems plausible that the CAF is lifted out to
the top level, and is evaluated in constant space (but infinite time).

So it seems, that as a CAF, the generated code does not attempt to
memoize the input infinite list.  It may be worth noting that if
"repeat" is replaced with "replicate 10000", "replicate 1000000",
... memory usage grows with the size of the generated list.  Only
the infinite list when pre-computed as a CAF seems to "run" in
constant space.  (Scare quotes around "run" since in this it
never completes the computation.  You either never finish,
or use unbounded space, pick your poison).

------ snip ------
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE ViewPatterns #-}

module Main (main) where
import System.Environment
import System.Timeout
import Control.Concurrent
import Control.Concurrent.MVar
import Data.List

partitionEithers :: [Either a b] -> ([a],[b])
partitionEithers = foldr go ([],[])
  where
    go (Left  x) ~(xs,ys) = (x:xs,ys)
    go (Right y) ~(xs,ys) = (xs,y:ys)

main = do
    n <- getArgs >>= \case
      []  -> return 100
      a:_ -> return $ read a
    m <- newEmptyMVar
    forkIO $ do
        let (length -> lx, length -> ly) = partitionEithers $ repeat $ Left ()
        print lx
        print ly
        putMVar m ()
    timeout n $ takeMVar m
------ snip ------


> On Nov 8, 2018, at 1:13 PM, Tom Ellis <tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk> wrote:
> 
> I must admit I'm stumped!  I don't see any significant difference between
> those two programs.
> 
> On Thu, Nov 08, 2018 at 11:04:34AM -0500, Tyson Whitehead wrote:
>> Constant memory code (RES 6MB):
>> 
>>   {-# LANGUAGE ViewPatterns #-}
>> 
>>   module Main (main) where
>> 
>>   import Data.Either
>> 
>>   (length -> lx,length -> ly) = partitionEithers (repeat $ Left ())
>> 
>>   main = do
>>       print lx
>>       print ly
>> 
>> Unbounded memory:
>> 
>>   module Main (main) where
>> 
>>   import Data.Either
>> 
>>   (xs, ys) = partitionEithers (repeat $ Left ())
>> 
>>   main = do
>>       print $ length xs
>>       print $ length ys

-- 
	Viktor.



More information about the Haskell-Cafe mailing list