module Render where import Control.Monad (forM_) import Data.List import Data.Array ((!)) import GHC.Exts import Graphics.UI.SDL as SDL import Graphics.UI.SDL.Image as SDLi import Graphics.UI.SDL.TTF as TTF import Graphics.UI.SDL.Mixer as Mix import FRP.Yampa.Geometry import RenderPlayer import RenderBall import RenderGame import RenderUtil import Object import States import BasicTypes init = do SDL.init [SDL.InitVideo] TTF.init screen <- SDL.setVideoMode (truncate winWidth) (truncate winHeight) 32 [] openAudio 22050 AudioS16Sys 2 4096 pitch <- pitchRessources screen fonts <- fontsRessources balls <- ballRessources screen (tockWav, kickWav, whistleWav) <- soundRessources return (screen, pitch, fonts, balls, tockWav, kickWav, whistleWav) exit = do closeAudio TTF.quit SDL.quit renderObjects param oos (screen, pitch, fonts, balls, tockWav, kickWav, whistleWav) = do cf <- chalkFontsRessources cfb <- bigChalkFonts forM_ sorted $ \os -> case os of OOSBall oosPos oosVelocity oosBounced oosPState -> do renderBall param screen balls tockWav oosPos oosBounced renderBallDebug screen oosPState cf (point3Z oosPos) OOSPlayer oosPos oosVel oosAcc oosKicked oosSelected oosDesignated oosRadius (oosTeam, oosBorder, oosBody) (PlayerInfo oosNumber _ bpOff bpDef _ _ _) oosDir (bs, bsp) (ts, tsp) oosOnFoot -> do renderPlayer param screen oosPos oosDir oosSelected oosNumber oosBody oosBorder oosBorder oosKicked (ts==TSNonAI) oosDesignated fonts kickWav renderPlayerDebug screen oosSelected oosNumber bs ts oosBody cf bpDef bpOff oosTeam OOSGame oosGameTime oosGameScore oosGameState oosAttacker _ -> renderGame param screen oosGameTime oosGameScore oosGameState oosAttacker cfb (fonts ! 4) whistleWav where sorted = sortWith (point3Z . oosPos) oos render param oos (screen, pitch, fonts, balls, tockWav, kickWav, whistleWav) = do -- putStrLn $ "Anzahl: " ++ show (length oos) SDL.blitSurface pitch Nothing screen Nothing renderObjects param oos (screen, pitch, fonts, balls, tockWav, kickWav, whistleWav) SDL.flip screen renderStartMsg (screen,_, fonts,_,_,_,_) = do let font = fonts ! 4 let color = colorFromPixel $ rgbColor 255 255 1 fontSurface <- TTF.renderTextSolid font ("PRESS TO START") color SDL.blitSurface fontSurface Nothing screen (Just $ Rect 250 400 100 100) SDL.flip screen renderEndMsg (screen,_, fonts,_,_,_,whistle) = do let font = fonts ! 4 let color = colorFromPixel $ rgbColor 255 255 1 fontSurface <- TTF.renderTextSolid font ("GAME OVER, TRY AGAIN (Y/N)") color playChannel (1) whistle 0 SDL.blitSurface fontSurface Nothing screen (Just $ Rect 200 400 100 100) SDL.flip screen