[Haskell-cafe] Inconsistent window updates with SDL library
Michael Serra
mk.serra at gmail.com
Tue May 17 02:42:02 CEST 2011
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]]
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20110516/367e6a01/attachment.htm>
More information about the Haskell-Cafe
mailing list