aboutsummaryrefslogtreecommitdiff
path: root/demos
diff options
context:
space:
mode:
Diffstat (limited to 'demos')
-rw-r--r--demos/pong/Main.hs81
-rw-r--r--demos/pong/Pong.hs141
-rw-r--r--demos/pong/Setup.hs3
3 files changed, 0 insertions, 225 deletions
diff --git a/demos/pong/Main.hs b/demos/pong/Main.hs
deleted file mode 100644
index a9dfcdd..0000000
--- a/demos/pong/Main.hs
+++ /dev/null
@@ -1,81 +0,0 @@
1module Main where
2
3import Data.Maybe (mapMaybe)
4import Graphics.Rendering.OpenGL.GL (($=))
5import qualified Graphics.Rendering.OpenGL.GL as GL
6import Pong
7import Spear.App
8import Spear.Game
9import Spear.Math.AABB
10import Spear.Math.Spatial2
11import Spear.Math.Vector
12import Spear.Window
13
14data GameState = GameState
15 { window :: Window,
16 world :: [GameObject]
17 }
18
19main =
20 withWindow (900, 600) (2, 0) (Just "Pong") initGame $
21 loop step
22
23initGame :: Window -> Game () GameState
24initGame window = do
25 gameIO $ do
26 GL.clearColor $= GL.Color4 0.7 0.5 0.7 1.0
27 GL.matrixMode $= GL.Modelview 0
28 GL.loadIdentity
29 return $ GameState window newWorld
30
31step :: Elapsed -> Dt -> [InputEvent] -> Game GameState Bool
32step elapsed dt inputEvents = do
33 gs <- getGameState
34 gameIO . process $ inputEvents
35 let events = translate inputEvents
36 modifyGameState $ \gs ->
37 gs
38 { world = stepWorld elapsed dt events (world gs)
39 }
40 getGameState >>= \gs -> gameIO . render $ world gs
41 return (not $ exitRequested inputEvents)
42
43render world = do
44 GL.clear [GL.ColorBuffer]
45 mapM_ renderGO world
46
47renderGO :: GameObject -> IO ()
48renderGO go = do
49 let (AABB2 (Vector2 xmin' ymin') (Vector2 xmax' ymax')) = aabb go
50 (Vector2 xcenter ycenter) = pos go
51 (xmin, ymin, xmax, ymax) = (f2d xmin', f2d ymin', f2d xmax', f2d ymax')
52 GL.preservingMatrix $ do
53 GL.translate (GL.Vector3 (f2d xcenter) (f2d ycenter) 0)
54 GL.renderPrimitive (GL.TriangleStrip) $ do
55 GL.vertex (GL.Vertex2 xmin ymax)
56 GL.vertex (GL.Vertex2 xmin ymin)
57 GL.vertex (GL.Vertex2 xmax ymax)
58 GL.vertex (GL.Vertex2 xmax ymin)
59
60process = mapM_ procEvent
61
62procEvent (Resize w h) = do
63 GL.viewport $= (GL.Position 0 0, GL.Size (fromIntegral w) (fromIntegral h))
64 GL.matrixMode $= GL.Projection
65 GL.loadIdentity
66 GL.ortho 0 1 0 1 (-1) 1
67 GL.matrixMode $= GL.Modelview 0
68procEvent _ = return ()
69
70translate = mapMaybe translate'
71
72translate' (KeyDown KEY_LEFT) = Just MoveLeft
73translate' (KeyDown KEY_RIGHT) = Just MoveRight
74translate' (KeyUp KEY_LEFT) = Just StopLeft
75translate' (KeyUp KEY_RIGHT) = Just StopRight
76translate' _ = Nothing
77
78exitRequested = any (== (KeyDown KEY_ESC))
79
80f2d :: Float -> GL.GLdouble
81f2d = realToFrac
diff --git a/demos/pong/Pong.hs b/demos/pong/Pong.hs
deleted file mode 100644
index accc75d..0000000
--- a/demos/pong/Pong.hs
+++ /dev/null
@@ -1,141 +0,0 @@
1module Pong
2 ( GameEvent (..),
3 GameObject,
4 newWorld,
5 stepWorld,
6 aabb,
7 )
8where
9
10import Data.Monoid (mconcat)
11import GHC.Float (double2Float)
12import Spear.Math.AABB
13import Spear.Math.Spatial2
14import Spear.Math.Vector
15import Spear.Step
16
17-- Configuration
18
19padSize = vec2 0.05 0.02
20
21ballSize = 0.01
22
23ballVelocity = vec2 0.3 0.3
24
25playerSpeed = 0.7
26
27initialEnemyPos = vec2 0.5 0.9
28
29initialPlayerPos = vec2 0.5 0.1
30
31initialBallPos = vec2 0.5 0.5
32
33-- Game events
34
35data GameEvent
36 = MoveLeft
37 | MoveRight
38 | StopLeft
39 | StopRight
40 deriving (Eq, Ord)
41
42-- Game objects
43
44data GameObject = GameObject
45 { aabb :: AABB2,
46 obj :: Obj2,
47 gostep :: Step [GameObject] [GameEvent] GameObject GameObject
48 }
49
50instance Spatial2 GameObject where
51 getObj2 = obj
52 setObj2 s o = s {obj = o}
53
54stepWorld :: Elapsed -> Dt -> [GameEvent] -> [GameObject] -> [GameObject]
55stepWorld elapsed dt evts gos = map (update elapsed dt evts gos) gos
56
57update :: Elapsed -> Dt -> [GameEvent] -> [GameObject] -> GameObject -> GameObject
58update elapsed dt evts gos go =
59 let (go', s') = runStep (gostep go) elapsed dt gos evts go
60 in go' {gostep = s'}
61
62ballBox, padBox :: AABB2
63ballBox = AABB2 (vec2 (- s) (- s)) (vec2 s s) where s = ballSize
64padBox = AABB2 (- padSize) padSize
65
66obj2 = obj2FromVectors unitx2 unity2
67
68newWorld =
69 [ GameObject ballBox (obj2 initialBallPos) $ stepBall ballVelocity,
70 GameObject padBox (obj2 initialEnemyPos) stepEnemy,
71 GameObject padBox (obj2 initialPlayerPos) stepPlayer
72 ]
73
74-- Ball steppers
75
76stepBall vel = collideBall vel .> moveBall
77
78collideBall :: Vector2 -> Step [GameObject] e GameObject (Vector2, GameObject)
79collideBall vel = step $ \_ dt gos _ ball ->
80 let (AABB2 pmin pmax) = aabb ball `aabbAdd` pos ball
81 collideCol = x pmin < 0 || x pmax > 1
82 collideRow = y pmin < 0 || y pmax > 1 || any (collide ball) (tail gos)
83 negx v@(Vector2 x y) = if collideCol then vec2 (- x) y else v
84 negy v@(Vector2 x y) = if collideRow then vec2 x (- y) else v
85 vel' = negx . negy $ vel
86 delta = dt -- A small delta to apply when collision occurs.
87 adjustX = if collideCol then scale delta (vec2 (x vel) 0) else vec2 0 0
88 adjustY = if collideRow then scale delta (vec2 0 (y vel)) else vec2 0 0
89 in ((vel' + adjustX + adjustY, ball), collideBall vel')
90
91collide go1 go2 =
92 let (AABB2 (Vector2 xmin1 ymin1) (Vector2 xmax1 ymax1)) =
93 aabb go1 `aabbAdd` pos go1
94 (AABB2 (Vector2 xmin2 ymin2) (Vector2 xmax2 ymax2)) =
95 aabb go2 `aabbAdd` pos go2
96 in not $
97 xmax1 < xmin2 || xmin1 > xmax2
98 || ymax1 < ymin2
99 || ymin1 > ymax2
100
101aabbAdd (AABB2 pmin pmax) p = AABB2 (p + pmin) (p + pmax)
102
103moveBall :: Step s e (Vector2, GameObject) GameObject
104moveBall = step $ \_ dt _ _ (vel, ball) -> (move (scale dt vel) ball, moveBall)
105
106-- Enemy stepper
107
108stepEnemy = movePad
109
110movePad :: Step s e GameObject GameObject
111movePad = step $ \elapsed _ _ _ pad ->
112 let p = vec2 px 0.9
113 px =
114 double2Float (sin elapsed * 0.5 + 0.5)
115 * (1 - 2 * x padSize)
116 + x padSize
117 in (setPos p pad, movePad)
118
119-- Player stepper
120
121stepPlayer = sfold moveGO .> clamp
122
123moveGO =
124 mconcat
125 [ switch StopLeft sid MoveLeft (moveGO' $ vec2 (- playerSpeed) 0),
126 switch StopRight sid MoveRight (moveGO' $ vec2 playerSpeed 0)
127 ]
128
129moveGO' :: Vector2 -> Step s e GameObject GameObject
130moveGO' dir = step $ \_ dt _ _ go -> (move (scale dt dir) go, moveGO' dir)
131
132clamp :: Step s e GameObject GameObject
133clamp = spure $ \go ->
134 let p' = vec2 (clamp' x s (1 - s)) y
135 (Vector2 x y) = pos go
136 clamp' x a b
137 | x < a = a
138 | x > b = b
139 | otherwise = x
140 (Vector2 s _) = padSize
141 in setPos p' go
diff --git a/demos/pong/Setup.hs b/demos/pong/Setup.hs
deleted file mode 100644
index e8ef27d..0000000
--- a/demos/pong/Setup.hs
+++ /dev/null
@@ -1,3 +0,0 @@
1import Distribution.Simple
2
3main = defaultMain