[reactive] reactive (-glut) problems?

Balazs Komuves bkomuves at gmail.com
Tue Dec 2 07:58:01 EST 2008


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
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/reactive/attachments/20081202/8c6ec0a5/attachment.htm


More information about the Reactive mailing list