aboutsummaryrefslogtreecommitdiff
path: root/demos/pong/Main.hs
diff options
context:
space:
mode:
Diffstat (limited to 'demos/pong/Main.hs')
-rw-r--r--demos/pong/Main.hs86
1 files changed, 86 insertions, 0 deletions
diff --git a/demos/pong/Main.hs b/demos/pong/Main.hs
new file mode 100644
index 0000000..8c379ec
--- /dev/null
+++ b/demos/pong/Main.hs
@@ -0,0 +1,86 @@
1module Main where
2
3import Pong
4
5import Spear.Math.AABB
6import Spear.Math.Spatial2
7import Spear.Math.Vector
8import Spear.Game
9import Spear.Window
10
11import Data.Maybe (mapMaybe)
12import qualified Graphics.Rendering.OpenGL.GL as GL
13import Graphics.Rendering.OpenGL.GL (($=))
14
15data GameState = GameState
16 { wnd :: Window
17 , elapsed :: Double
18 , world :: [GameObject]
19 }
20
21main = do
22 result <- run
23 case result of
24 Left err -> putStrLn err
25 Right _ -> return ()
26
27run = withWindow (640,480) [] Window (2,0) (Just "Pong") initGame
28 $ loop (Just 30) step
29
30initGame wnd = do
31 gameIO $ do
32 GL.clearColor $= GL.Color4 0.7 0.5 0.7 1.0
33 GL.matrixMode $= GL.Modelview 0
34 GL.loadIdentity
35 return $ GameState wnd 0 newWorld
36
37step :: Dt -> Game GameState Bool
38step dt = do
39 gs <- getGameState
40 evts <- events (wnd gs)
41 gameIO . process $ evts
42 let evts' = translate evts
43 modifyGameState $ \ gs -> gs
44 { world = stepWorld (elapsed gs) dt evts' (world gs)
45 , elapsed = elapsed gs + realToFrac dt }
46 getGameState >>= \gs -> gameIO . render $ world gs
47 return (not $ exitRequested evts)
48
49render world = do
50 GL.clear [GL.ColorBuffer]
51 mapM_ renderGO world
52 swapBuffers
53
54renderGO :: GameObject -> IO ()
55renderGO go = do
56 let (AABB2 (Vector2 xmin' ymin') (Vector2 xmax' ymax')) = aabb go
57 (Vector2 xcenter ycenter) = pos go
58 (xmin,ymin,xmax,ymax) = (f2d xmin', f2d ymin', f2d xmax', f2d ymax')
59 GL.preservingMatrix $ do
60 GL.translate (GL.Vector3 (f2d xcenter) (f2d ycenter) 0)
61 GL.renderPrimitive (GL.TriangleStrip) $ do
62 GL.vertex (GL.Vertex2 xmin ymax)
63 GL.vertex (GL.Vertex2 xmin ymin)
64 GL.vertex (GL.Vertex2 xmax ymax)
65 GL.vertex (GL.Vertex2 xmax ymin)
66
67process = mapM_ procEvent
68procEvent (Resize w h) = do
69 GL.viewport $= (GL.Position 0 0, GL.Size (fromIntegral w) (fromIntegral h))
70 GL.matrixMode $= GL.Projection
71 GL.loadIdentity
72 GL.ortho 0 1 0 1 (-1) 1
73 GL.matrixMode $= GL.Modelview 0
74procEvent _ = return ()
75
76translate = mapMaybe translate'
77translate' (KeyDown KEY_LEFT) = Just MoveLeft
78translate' (KeyDown KEY_RIGHT) = Just MoveRight
79translate' (KeyUp KEY_LEFT) = Just StopLeft
80translate' (KeyUp KEY_RIGHT) = Just StopRight
81translate' _ = Nothing
82
83exitRequested = any (==(KeyDown KEY_ESC))
84
85f2d :: Float -> GL.GLdouble
86f2d = realToFrac \ No newline at end of file