problem with Graphics.HGL

asilovy asilovy at hotmail.com
Fri Dec 15 17:34:52 EST 2006


Hello,

I'm trying some stuffs with the Graphics.HGL library and have a question. I
wonder if someone could help me with it.

I'm trying to write some Win32 application using openWindowEx. I see it has
a parameter to (eventually) define a timer. On the other hand, the
maybeGetWindowEvent function is used to get "notified" of different events
such as mouse button pressed, key pressed, resizing...

I don't understand the special status of the timer. Why is it not an event
like the others. It does'nt sound right to me. As I understand it, you have
to wait for a timer tick rather than being informed by a timer event.

For instance, I've written a small test program that uses the timer to draw
some random "stars" on a window. Eventually, when the user presses the mouse
button, the window is closed.

But, as you can try, if you trigger a lot of events (by, for instance,
moving the mouse a lot) BEFORE pressing the mouse button those events,
although I don't treat them, will have to be processed with the delays of
the timer before the mouse clic can be treated. And so, the window takes a
long time to close.

I'm I misunderstanding something ? And is there another way to treat the
timer ?

Thanks for your answer

Alain

{---------------------------------------------------------------------------------------
Draws randomly colored stars at random places
Uses Events from :
http://haskell.org/ghc/docs/latest/html/libraries/HGL/Graphics-HGL-Window.html#t%3AEvent
-}
import Graphics.HGL
import Hugs.Prelude
import System.Random
import Graphics.HGL.Win32.Types
import Control.Monad
import Data.Maybe

main = runGraphics myWin

myWin = do
  w <- openWindowEx "TestWindow" Nothing (400,400) DoubleBuffered (Just 100)
  let
    loop n = do
      x0 <- randomRIO (0, 39)
      y0 <- randomRIO (0, 39)
      couleur <- randomRIO (0, 0x00FFFFFF)
      let
        (x, y) = (x0 * 10, y0 * 10)
        c  = if mod couleur 10 == 0 then couleur else 0 -- 1/10 will be
colored
      drawInWindow w $ withRGB (toRGB (fromInt c)) $ ellipse (x, y) (x + 9,
y + 9)
      e <- maybeGetWindowEvent w                    -- some Event ?
      when (isJust e) $                             -- yes...
        case fromJust e of                          -- which ?
          Button _ _ _            -> closeWindow w  -- mouse button
          _                       -> return ()      -- something else ->
nothing to do
      getWindowTick w                               -- wait and...
      loop (n + 1)                                  -- loop
  loop 0
--------------------------------------------------------------------------------------


-- 
View this message in context: http://www.nabble.com/problem-with-Graphics.HGL-tf2829855.html#a7900522
Sent from the Haskell - Libraries mailing list archive at Nabble.com.



More information about the Libraries mailing list