module RenderGame where import Data.Array import Control.Monad import Data.Bits import Data.Int import FRP.Yampa.Geometry import Graphics.UI.SDL as SDL import Graphics.UI.SDL.TTF as SDLt import Graphics.UI.SDL.Mixer as Mix import RenderUtil import States import Message renderGame param surface t (scoreHome, scoreAway) (gState, gStateParam) attacker font bigfont whistle = do let color = colorFromPixel $ rgbColor 255 255 1 let tt = truncate t let (min, sec) = (tt `div` 60, tt `mod` 60) :: (Int, Int) fontSurface <- SDLt.renderTextSolid font ("Score " ++ show scoreHome ++ "-" ++ show scoreAway ++ " " ++ show min ++ "min " ++ show sec ++ "sec") color when (gState == GSKickOff && shouldWhistle gStateParam) $ do playChannel (1) whistle 0 >> return () SDL.blitSurface fontSurface Nothing surface (Just $ Rect 850 60 950 60) when (gState == GSKickOff && scoreHome + scoreAway > 0) $ do goalSurface <- SDLt.renderTextSolid bigfont ("GOAL!!") color SDL.blitSurface goalSurface Nothing surface (Just $ Rect 380 400 100 100) return () return True shouldWhistle (GPTeamPosition _ _ _ w) = w