-- a basic rocks game -- -- (c) 2009 Clara L\"oh, Andres L\"oh module Main where import System.Environment import System.Console.GetOpt import Control.Monad import Data.Maybe import qualified Control.Monad.State as S import qualified Control.Monad.Reader as R import Control.Monad.Trans import qualified Graphics.UI.SDL as SDL import qualified Graphics.UI.SDL.TTF as SDL.TTF import qualified Graphics.UI.SDL.Mixer as SDL.Mixer import qualified Graphics.Rendering.OpenGL as GL import Graphics.Rendering.OpenGL (($=)) import Data.Word -- import rox modules -- import FsoStatesInterface import StaticInterface -- import Static -- the main game loop import Game -- some global settings import Config -- additional modules providing debugging functions and option handling import Debug import Options -- for rendering the title import RenderTitle -- | Initialising SDL and OpenGL -- (handling graphics, user input, audio). initSDL :: Options -> IO () initSDL opts = do -- initialization calls for SDL SDL.init [SDL.InitEverything] SDL.TTF.init -- set up audio when (audio opts) $ do SDL.Mixer.openAudio 44100 SDL.Mixer.AudioS16Sys 2 4096 SDL.Mixer.allocateChannels 8 -- todo! adapt number of channels! return () -- it is recommended to set the GL attributes prior to setting the video -- mode via SDL ... SDL.glSetAttribute SDL.glRedSize 8 SDL.glSetAttribute SDL.glGreenSize 8 SDL.glSetAttribute SDL.glBlueSize 8 SDL.glSetAttribute SDL.glBufferSize 32 -- the following requests double buffering; it is then not required to -- pass a double buffer flag to setVideoMode below SDL.glSetAttribute SDL.glDoubleBuffer 1 -- this sets the video mode and opens a window SDL.setVideoMode maxXview maxYview 32 ((if fullscreen opts then (SDL.Fullscreen :) else id) [SDL.OpenGL]) -- this sets how much of our window we want to handle via OpenGL (all of it) GL.viewport $= (GL.Position 0 0, GL.Size (fromIntegral maxXview) (fromIntegral maxYview)) -- set up OpenGL for 2D mode GL.matrixMode $= GL.Projection GL.loadIdentity GL.ortho 0 (fromIntegral maxXview) (fromIntegral maxYview) 0 (-1.0) 1 GL.matrixMode $= GL.Modelview 0 GL.loadIdentity GL.translate (GL.Vector3 (0 :: Float) 0 0) -- we always want blending enabled -- note that if we don't, -- this should be moved into the game-specific rendering functions GL.blend $= GL.Enabled GL.blendEquation $= GL.FuncAdd GL.blendFunc $= (GL.SrcAlpha, GL.OneMinusSrcAlpha) -- verify that we got double buffering working db <- GL.get GL.doubleBuffer debug_msg opts $ "double buffering: " ++ show db return () main :: IO () main = do -- turn command line arguments into options args <- getArgs let (xs, _, _) = getOpt Permute optdescrs args let opts = foldl (flip ($)) defaultOptions xs -- print only help message? if help opts then putStrLn $ usageInfo ("\n " ++ gametitle ++ "\n") optdescrs else do -- init SDL initSDL opts -- initialize joysticks nj <- SDL.countAvailable j <- if nj > 0 then do SDL.enableEvent SDL.SDLJoyAxisMotion False liftM Just (SDL.open 0) else return Nothing -- title sequence -- load background music titleChunk <- if audio opts then liftM Just $ bgSound >>= SDL.Mixer.loadWAV else return Nothing -- background music when (audio opts) $ do SDL.Mixer.playChannel 0 (fromJust titleChunk) (-1) return () -- title images renderTitle -- start the actual game putStrLn "start game!" startGame (opts { joystick = j }) titleChunk `seq` SDL.quit -- subtle hack: prevent ghc from garbage collecting titleChunk