[grapefruit] Dynamic switching within a collection of signals.

Neal Alexander relapse.dev at gmx.com
Sun Jul 19 06:50:15 EDT 2009


Yea, incremental signals with a set seems like the best way to go, thanks.

I'm having trouble with the memory usage at the moment though. Every 10 
seconds or so the mem usage doubled when using sampled signals. The 
'DSignal era ()' frame event had constant memory usage by itself though.

I isolated the code into this small test and now both circuits grow in 
memory usage somehow. Heap profiling with +RTS -p hy shows Integer as 
the only entry on the circuit named "bad", and i think its internal to 
some library function because the code only uses the empty tuple type.

Tested with the darcs repository version of grapefruit, and compiled the 
program with ghc -O2 -fvia-c -optc-O2 -funbox-strict-fields -threaded 
and without any options as well.

{-# 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 :: IORef () -> forall era. Circuit era (DSignal era ()) ()
display output = consume . D.consumer $ \() -> do
	writeIORef output (() `using` rnf)


void = const $ return ()
	
main = do
	a <- newIORef void
	b <- newIORef void
	c <- newIORef ()
	
	create (bad a b c) ()
	drawFrame <- readIORef a
	
	forever $ drawFrame() >> yield -- >> performGC
	
{--
worse a b c = proc () -> do

	frameEvent <- externalSink a -< ()
	tracker    <- externalSink b -< ()
	display c  -< frameEvent #> (S.construct 0 tracker)
	returnA    -< ()
--}

bad a _ c = proc () -> do

	frameEvent <- externalSink a -< ()
	display c  -< frameEvent
	returnA    -< ()

externalSink r = produce . D.producer $ (fromIO . writeIORef r)



Wolfgang Jeltsch wrote:
> Am Samstag, 18. Juli 2009 09:42 schrieb Neal Alexander:
>> Is there a way to dynamically switch between signals from a Data.IntMap
>> collection for example?
>>
>> I could be wrong, but doesn't the current applicative style of 'switch'
>> limit you to a pretty small amount of static inputs?
>>
>> For example, lets say you have 100 entities roaming around and you want any
>> one of their continuous positions to be trackable depending on a switch
>> state. Is this an overuse of signals? If not, what options do you currently
>> have?
> 
> Hello Neal,
> 
> it should be possible to switch between 100 different signals with switch. 
> However, this might not be very efficient.
> 
> Are those 100 entities of a similar kind (e.g., 100 monsters in a video game)? 
> Then I wouldn’t use, for example, a set of 100 signals but a single signal 
> whose values are sets of 100 entries each. Using incremental signals 
> (implemented in the development version of Grapefruit) might be advisable.
> 
> I don’t know to what amount this answers your question since I don’t have 
> detailed information about your problem. I’d hope to hear from you further.
> 
> By the way, could you please send your mails in plain text or at least in 
> plain text plus HTML instead of HTML only? If I look at your mails, I only 
> see the footer added by the mailing list software. I always have to manually 
> switch to HTML to see the actual content. In addition, HTML-only mails might 
> not get properly archived by Mailman.
> 
> Best wishes,
> Wolfgang
> 
> _______________________________________________
> Grapefruit mailing list
> Grapefruit at projects.haskell.org
> http://projects.haskell.org/cgi-bin/mailman/listinfo/grapefruit



More information about the Grapefruit mailing list