producing and consuming lists

Hal Daume III hdaume@ISI.EDU
Tue, 5 Nov 2002 15:59:46 -0800 (PST)


Hrm.  This is interesting.  So one option you already considered would be
to put the writing inside 'streams', which probably should be
disprefered.  Have you considered doing something like:

streams :: (Int -> Bool, Int -> Bool) -> (Int,Int) ->
           [(Maybe Int,Maybe Int)]
streams (p,q) (x,y)
    | p x && p y = (Just x , Just y ) : xs
    | p x        = (Just x , Nothing) : xs
    | p y        = (Nothing, Just y ) : xs
    | otherwise  = xs
    where xs = streams (p,q) ((x+y),(y-x))

With this setup, I think you can write your own writefile function which
looks something like:

writeTwoFiles f1 f2 (p',q') stream = do
    h1 <- openFile f1 WriteMode
    h2 <- openFile f2 WriteMode
    writeFiles' h1 h2 stream
    hClose h1
    hClose h2
    where writeFiles' h1 h2 ((Just x,Just y):xs) 
              | p' x && p' y = do hPutStr h1 $ show x
                                  hPutStr h2 $ show y
                                  writeFiles' h1 h2 xs
              | p' x = do hPutSTr h1 $ show x
                          writeFiles' h1 h2 (zip (map fst xs) (repeat
                                                  Nothing)
              | p' y = do hPutSTr h2 $ show y
                          writeFiles' h1 h2 (zip (repeat Nothing)
                                                 (map snd xs))
              | otherwise = return ()
          writeFiles' h1 h2 ((Just x,Nothing):xs) = ...

where you essentially ignore the nothings.

I think, but I'm not sure, that this will allow the old stuff to be
garbage collected.  In practice, you don't get too much useless junk
generated because we don't append the (Nothing,Nothing) pair to the list
(erm, "prepend").  But what's more important, I think you only evaluate
the same amount of each at any given time, thus allowing GC to gobble up
the old stuff.

An expert might be able to prove me wrong, though, or you could try this
and profile it and see if it works or not :)

 - Hal

--
Hal Daume III

 "Computer science is no more about computers    | hdaume@isi.edu
  than astronomy is about telescopes." -Dijkstra | www.isi.edu/~hdaume

On Tue, 5 Nov 2002, Jorge Adriano wrote:

> I might have been not very clear in my last mail. I decided to post again, and 
> go straight to the point, with some small examples.
> 
> Consider the following function streams.
> 
> streams :: (Int->Bool, Int->Bool)->(Int, Int)->([Int],[Int])
> streams (p,q) (x,y) = (xs',ys')
>     where
>     (xs,ys) = streams (p,q) ((x+y),(y-x))
>     xs' = if p x then x:xs else xs
>     ys' = if q y then y:xs else ys
> 
> 
> - produces a pair of ('infinite') lists
> - produced lists are not indepentent (you need to calculate elements of one 
> list to calculate elements of the other)
> - in each recursive call an element is added to the 1st/2nd list iff  it 
> satisfies a given (Int->Bool) function p/q
> 
> How should one consume (part of) both lists, avoiding space leaks?
> 
> A particular example of consuming both lists might be writing them to files:
> main :: IO()
> main = do
>        let (s1,s2)=stream ... -- stream applied to some arguments (p,q) (x,y)
>            p' = ... 
>            q' = ... 
>        writeFile "f1.txt" (show$ takeWhile p' s1)
>        writeFile "f2.txt" (show$ takeWhile q' s2)
> 
> In this example all elements of s2 required to evaluate (takeWhile p' s1) are 
> kept in memory, until the first file is writen. Notice that writing one 
> element from s1 and one from s2 successively might still cause space leaks to 
> arise. Fusing the consuming functions with the producer is a possible, but 
> IMO dirty, way out. 
> 
> If my question doesn't seem to make sense for any reason, please tell me, 
> maybe I am missing something obvious here. 
> Thanks,
> J.A.
> 
> 
> 
> 
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>