Inconsistent window updates with SDL library

Greetings Haskellers, I'm relatively new to the language and I'm writing a basic game of life simulation to try out the SDL bindings. The program updates the window with the next generation of cells each time you press 'n', and the problem I'm finding is that every so often the window stops updating. The program continues; refreshing the window (by moving it, say) updates it to the correct current state. I thought there must be a big problem with my code, but found the same behavior with lesson 20https://github.com/snkkid/LazyFooHaskellof the SDL lazyfoo tutorials (the animation test). Can anyone explain what is causing this? I hope to hear I've made some obvious mistake, rather than discover any limitation with the useful SDL bindings..

Oh, in case the code would be helpful.. ;) import Data.Set (toList, fromList, intersection, size) import Data.List ((\\)) import System.Random (randomRIO) import Data.Word (Word32) import Graphics.UI.SDL as SDL main = do SDL.init [InitVideo, InitTimer, InitEventthread] w <- setVideoMode 1440 900 32 [] setCaption "LIFE" "life" eventLoop w cells quit eventLoop w cs = do drawCells w cs e <- waitEventBlocking checkEvent e where checkEvent (KeyUp (Keysym SDLK_ESCAPE _ _)) = return () checkEvent (KeyUp (Keysym SDLK_n _ _)) = eventLoop w $ nextgen cs checkEvent _ = eventLoop w cs drawCells w cs = do clearScreen s <- createRGBSurface [SWSurface] size size 32 0 0 0 0 sequence $ map (draw s) $ scale cs SDL.flip w where clearScreen = fillRect w (Just $ Rect 0 0 1440 900) $ Pixel 0x0 rect x y = Just $ Rect x y size size scale = map (\(x,y) -> (x * size, y * size)) size = 16 draw s (x,y) = do r <- randomRIO (0::Int, 0xFFFFFF) fillRect s (rect 0 0) $ Pixel (fromIntegral r :: Word32) blitSurface s (rect 0 0) w $ rect x y -------------------------------------------------------------------------------- cells = [(25,14),(26,14),(25,15),(24,15),(25,16)] nextgen cs = (filter (live cs) cs) ++ births cs live cs c = size neighbors > 1 && size neighbors < 4 where neighbors = adj c `intersection` fromList cs births cs = (filter neighbors3 allAdjacent) \\ cs where allAdjacent = nub $ concatMap (toList . adj) cs neighbors3 c = size (neighbors c) == 3 neighbors c = adj c `intersection` fromList cs nub = toList . fromList adj (x,y) = fromList $ tail [(a,b) | a <- [x,x+1,x-1], b <- [y,y+1,y-1]]

On 17/05/11 01:42, Michael Serra wrote:
eventLoop w cs = do drawCells w cs e <- waitEventBlocking checkEvent e where checkEvent (KeyUp (Keysym SDLK_ESCAPE _ _)) = return () checkEvent (KeyUp (Keysym SDLK_n _ _)) = eventLoop w $ nextgen cs checkEvent _ = eventLoop w cs
Your code is a bit strange. It redraws the window every time there is a window event (whether its an unrelated key-down or a relevant event). So whenever there's some window events, your window rapidly redraws (and in a different set of random colours). I'm not sure this is the intended behaviour? I didn't find any point at which the program didn't advance and redraw when I released 'n' -- but I'm not sure if that was exactly the problem you're having. Can you clarify exactly what the problem is? Is that you're not seeing the keypresses being processed, or is it that you expect more redrawing than there is, etc? Thanks, Neil.
participants (2)
-
Michael Serra
-
Neil Brown