[grapefruit] Dynamic switching within a collection of signals.
Neal Alexander
relapse.dev at gmx.com
Sun Jul 19 22:27:40 EDT 2009
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 -< ()
------------------------------------------------------
-------------- next part --------------
An embedded and charset-unspecified text was scrubbed...
Name: test3.prof
Url: http://projects.haskell.org/pipermail/grapefruit/attachments/20090719/0f83f5f2/attachment.txt
More information about the Grapefruit
mailing list