[grapefruit] growing heap usage (was: Re: Dynamic switching within a collection of signals.)

Wolfgang Jeltsch g9ks157k at acme.softbase.org
Tue Jul 21 15:30:32 EDT 2009


Am Montag, 20. Juli 2009 04:27 schrieb Neal Alexander:
> Heres a smaller test - memory usage grows non-stop still. I attached the
> profiling info since the columns are pretty wide.
>
> Internal.Signal.Discrete.Vista.consumer and producer are using about 50%
> of the memory total each.
>
> The +RTS -p -hy graph still shows Integer as being the most allocated
> type oddly.
>
> -----------------------------------------------------
> {-# LANGUAGE RankNTypes, Arrows, TypeOperators, BangPatterns #-}
>
> import FRP.Grapefruit.Circuit
> import FRP.Grapefruit.Signal
> import FRP.Grapefruit.Signal.Discrete as D
> import FRP.Grapefruit.Signal.Continuous as C
> import FRP.Grapefruit.Signal.Segmented as S
> import FRP.Grapefruit.Setup
> import Control.Arrow
> import Control.Monad
> import Control.Concurrent
> import Control.Concurrent.SampleVar
> import Control.Applicative
> import Control.Parallel.Strategies
> import System.Mem
> import Data.IORef
>
>
> display () = return ()
>
> genFrames f = fromIO $ forkIO (go f) >> return ()
> 	where go f = forever $ (f () >> yield)
>
> main = create bad () >> threadDelay 99999999
>
> cDisplay   = D.consumer display
> pGenFrames = D.producer genFrames
>
> bad = proc () -> do
>
> 	frameEvent         <- produce pGenFrames -< ()
> 	(consume cDisplay) -< frameEvent
> 	returnA            -< ()
>
> ------------------------------------------------------

I have to admit that I’m basically new to profiling. I did some heap profiling 
with your code, but this always showed me a graph with only one band: 
Internal.Signal.Discrete.Vista.CAF, even when having used -caf-all.

Do you know when the garbage collector starts collecting garbage? Only when 
there is no more free memory? This would explain the behavior.

A discrete signal is represented by a so-called vista internally. In the case 
of your small example, this vista is similar to a list with an element for 
each signal value. The producer produces the vista lazily, and the consumer 
consumes it. After the consumer has consumed certain “elements”, the garbage 
collector should be able to drop these elements.

If it doesn’t drop them after a short amount of time but only when there is no 
more free memory, we would have a serious problem. However, I wouldn’t want 
to “fix” Grapefruit in this case, since I’d think that it would be better 
to “fix” GHC to be more real-time friendly. Maybe garbage-collection could be 
done concurrently, removing garbage as it is produced.

I have also a remark regarding your code (although this seems to have nothing 
to do with the memory consumption problem). The producer is formed from the 
action genFrames which directly starts a thread that generates events by 
calling its argument f repeatedly.

This is not a good idea. It means that events are produced as soon as the 
circuit

    produce pGenFrames

is realized. At this time, the consumer isn’t ready yet. So the consumer might 
miss a few events. It only reacts to the events that follow these few initial 
events but nevertheless consumes the values of the initial events (This 
doesn’t matter in this case, because all values are ().). So it gets out of 
sync.

Events are only allowed to be produced after the circuit has been fully 
realized. The action passed to the producer shall only register the event 
handler for later use. Events shall be produced by a separate action that is 
called after Circuit.create. In the case of GUIs, this would be an event 
loop.

Best wishes,
Wolfgang



More information about the Grapefruit mailing list