aboutsummaryrefslogtreecommitdiff
path: root/demos/pong/Main.hs
blob: e9a6dc10bee51aab27d4526540ee00806447b25c (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
module Main where

import Pong

import Spear.Math.AABB
import Spear.Math.Spatial2
import Spear.Math.Vector
import Spear.Game
import Spear.Window

import Data.Maybe (mapMaybe)
import qualified Graphics.Rendering.OpenGL.GL as GL
import Graphics.Rendering.OpenGL.GL (($=))

data GameState = GameState
     { wnd     :: Window
     , elapsed :: Double
     , world   :: [GameObject]
     }

main = run
     $ withWindow (640,480) [] Window (2,0) (Just "Pong") initGame
     $ loop (Just 30) step

initGame wnd = do
         gameIO $ do
                GL.clearColor $= GL.Color4 0.7 0.5 0.7 1.0
                GL.matrixMode $= GL.Modelview 0
                GL.loadIdentity
         return $ GameState wnd 0 newWorld

step :: Dt -> Game GameState Bool
step dt = do
     gs <- getGameState
     evts <- events (wnd gs)
     gameIO . process $ evts
     let evts' = translate evts
     modifyGameState $ \ gs -> gs
                     { world = stepWorld (elapsed gs) dt evts' (world gs)
                     , elapsed = elapsed gs + realToFrac dt }
     getGameState >>= \gs -> gameIO . render $ world gs
     return (not $ exitRequested evts)

render world = do
       GL.clear [GL.ColorBuffer]
       mapM_ renderGO world
       swapBuffers

renderGO :: GameObject -> IO ()
renderGO go = do
         let (AABB2 (Vector2 xmin' ymin') (Vector2 xmax' ymax')) = aabb go
             (Vector2 xcenter ycenter) = pos go
             (xmin,ymin,xmax,ymax) = (f2d xmin', f2d ymin', f2d xmax', f2d ymax')
         GL.preservingMatrix $ do
            GL.translate (GL.Vector3 (f2d xcenter) (f2d ycenter) 0)
            GL.renderPrimitive (GL.TriangleStrip) $ do
               GL.vertex (GL.Vertex2 xmin ymax)
               GL.vertex (GL.Vertex2 xmin ymin)
               GL.vertex (GL.Vertex2 xmax ymax)
               GL.vertex (GL.Vertex2 xmax ymin)

process = mapM_ procEvent
procEvent (Resize w h) = do
          GL.viewport $= (GL.Position 0 0, GL.Size (fromIntegral w) (fromIntegral h))
          GL.matrixMode $= GL.Projection
          GL.loadIdentity
          GL.ortho 0 1 0 1 (-1) 1
          GL.matrixMode $= GL.Modelview 0
procEvent _ = return ()

translate = mapMaybe translate'
translate' (KeyDown KEY_LEFT)  = Just MoveLeft
translate' (KeyDown KEY_RIGHT) = Just MoveRight
translate' (KeyUp   KEY_LEFT)  = Just StopLeft
translate' (KeyUp   KEY_RIGHT) = Just StopRight
translate' _ = Nothing

exitRequested = any (==(KeyDown KEY_ESC))

f2d :: Float -> GL.GLdouble
f2d = realToFrac