reactive (-glut) problems?

Dear All, I'm trying to get my hands wet with the reactive library, but already the simplest example I cooked up is failing to work properly (and leaks memory, and uses relatively lots of cpu time). The problem appears when I try to merge my two events with `mappend`. One event should exit on pressing ESC, the other draws colored circles on pressing the left mouse button. They work correctly separately. Could somebody explain me what's happening, or whether I'm making a basic mistake? The code is below, I hope the formatting survives the various email systems. I don't know if that matters or not, but I'm using OS X. Thanks, Balazs module Main where
import Control.Monad import Data.Monoid
import FRP.Reactive import FRP.Reactive.GLUT.Adapter
import Graphics.Rendering.OpenGL hiding (normalize) import Graphics.UI.GLUT hiding (normalize,Char)
import System.Exit
-------------------------------------------------------
nop :: Monad m => m () nop = return ()
data Vec2 = Vec2 !Float !Float
(&+) (Vec2 x1 y1) (Vec2 x2 y2) = Vec2 (x1+x2) (y1+y2)
sinCosRadius a r = Vec2 (r * cos a) (r * sin a)
instance Vertex Vec2 where vertex (Vec2 x y) = vertex (Vertex2 x y)
-------------------------------------------------------
display :: Action -> Action display action = do clear [ ColorBuffer , DepthBuffer ]
siz@(Size xs ys) <- get windowSize matrixMode $= Projection loadIdentity let q = fromIntegral xs / fromIntegral ys r = 1 / q if q >= 1 then ortho 0 1 r 0 (-1) 1 else ortho 0 q 1 0 (-1) 1 viewport $= ( Position 0 0 , siz ) matrixMode $= Modelview 0 loadIdentity
action postRedisplay Nothing swapBuffers
data Col = RR | GG | BB
nextCol RR = GG nextCol GG = BB nextCol BB = RR
setCol RR = color (Color3 1 0 (0::Float)) setCol GG = color (Color3 0 1 (0::Float)) setCol BB = color (Color3 0 0 (1::Float))
drawWithCol col = do setCol col let center = Vec2 0.25 0.25 radius = 0.1 n = 32 renderPrimitive TriangleFan $ do vertex center let phi j = 2*pi * fromIntegral j / fromIntegral n forM_ [0..n] $ \i -> vertex (center &+ sinCosRadius (phi i) radius)
myUI :: UI -> Behaviour Action myUI ui = uiB where
mp = mousePosition ui lb = leftButtonPressed ui rb = leftButtonPressed ui ky = keyPressed ui
colE = mealy_ RR nextCol lb drawE = fmap drawWithCol colE
exitE = justE (fmap esc ky) where esc k = case k of Char '\ESC' -> Just exitSuccess _ -> Nothing
uiE = fmap display drawE `mappend` exitE uiB = stepper nop uiE
-------------------------------------------------------
main = do initialize "alma" [] initialWindowSize $= Size 512 384 initialDisplayMode $= [ RGBAMode , WithDepthBuffer , DoubleBuffered ] createWindow "reactive test" adapt myUI

It seems that the function 'justE' caused my problem. If I remove that, replacing the section at issue with exitE = fmap esc ky where
esc k = case k of Char '\ESC' -> exitSuccess _ -> nop
then the program works. However, there is a large
random delay, sometimes measured in seconds, before
processing the events in the second argument of
`mappend`. And it still leaks space. Any advice?
(all this is with reactive-0.9.6 and ghc 6.10.1)
Thanks,
Balazs
On Tue, Dec 2, 2008 at 1:58 PM, Balazs Komuves
Dear All,
I'm trying to get my hands wet with the reactive library, but already the simplest example I cooked up is failing to work properly (and leaks memory, and uses relatively lots of cpu time).
The problem appears when I try to merge my two events with `mappend`. One event should exit on pressing ESC, the other draws colored circles on pressing the left mouse button. They work correctly separately.
Could somebody explain me what's happening, or whether I'm making a basic mistake?
The code is below, I hope the formatting survives the various email systems. I don't know if that matters or not, but I'm using OS X.
Thanks, Balazs

I had experienced large delays at the first rendering of some shapes, that
were attributed to tessellation.
Perhaps the delays result from that? Are you displaying any shapes for the
first time?
Eyal
2008/12/3 Balazs Komuves
It seems that the function 'justE' caused my problem. If I remove that, replacing the section at issue with
exitE = fmap esc ky where
esc k = case k of Char '\ESC' -> exitSuccess _ -> nop
then the program works. However, there is a large random delay, sometimes measured in seconds, before processing the events in the second argument of `mappend`. And it still leaks space. Any advice? (all this is with reactive-0.9.6 and ghc 6.10.1)
Thanks, Balazs
On Tue, Dec 2, 2008 at 1:58 PM, Balazs Komuves
wrote: Dear All,
I'm trying to get my hands wet with the reactive library, but already the simplest example I cooked up is failing to work properly (and leaks memory, and uses relatively lots of cpu time).
The problem appears when I try to merge my two events with `mappend`. One event should exit on pressing ESC, the other draws colored circles on pressing the left mouse button. They work correctly separately.
Could somebody explain me what's happening, or whether I'm making a basic mistake?
The code is below, I hope the formatting survives the various email systems. I don't know if that matters or not, but I'm using OS X.
Thanks, Balazs
_______________________________________________ Reactive mailing list Reactive@haskell.org http://www.haskell.org/mailman/listinfo/reactive
participants (2)
-
Balazs Komuves
-
Eyal Lotem