diff options
Diffstat (limited to 'Demos/Pong')
-rw-r--r-- | Demos/Pong/Main.hs | 84 | ||||
-rw-r--r-- | Demos/Pong/Pong.hs | 133 |
2 files changed, 120 insertions, 97 deletions
diff --git a/Demos/Pong/Main.hs b/Demos/Pong/Main.hs index d51a324..22b1021 100644 --- a/Demos/Pong/Main.hs +++ b/Demos/Pong/Main.hs | |||
@@ -1,3 +1,5 @@ | |||
1 | {-# LANGUAGE MultiParamTypeClasses #-} | ||
2 | |||
1 | module Main where | 3 | module Main where |
2 | 4 | ||
3 | import Pong | 5 | import Pong |
@@ -5,52 +7,62 @@ import Pong | |||
5 | import Spear.App | 7 | import Spear.App |
6 | import Spear.Game | 8 | import Spear.Game |
7 | import Spear.Math.AABB | 9 | import Spear.Math.AABB |
8 | import Spear.Math.Matrix4 as Matrix4 hiding (position) | 10 | import Spear.Math.Matrix4 as Matrix4 |
9 | import Spear.Math.Spatial | 11 | import Spear.Math.Spatial |
10 | import Spear.Math.Spatial2 | 12 | import Spear.Math.Spatial2 |
11 | import Spear.Math.Vector | 13 | import Spear.Math.Vector |
14 | import Spear.Physics.Collision | ||
12 | import Spear.Render.Core.Pipeline | 15 | import Spear.Render.Core.Pipeline |
13 | import Spear.Render.Core.State | 16 | import Spear.Render.Core.State |
14 | import Spear.Render.Immediate | 17 | import Spear.Render.Immediate |
18 | import Spear.Sound.Sound | ||
19 | import Spear.Sound.State | ||
15 | import Spear.Window | 20 | import Spear.Window |
16 | 21 | ||
17 | import Control.Monad (when) | 22 | import Control.Monad (when) |
18 | import Data.Maybe (mapMaybe) | ||
19 | 23 | ||
20 | 24 | ||
21 | data GameState = GameState | 25 | data Pong = Pong |
22 | { window :: Window | 26 | { viewProjection :: Matrix4 |
23 | , renderCoreState :: RenderCoreState | 27 | , backgroundMusic :: SoundSource |
24 | , immRenderState :: ImmRenderState | ||
25 | , viewProjection :: Matrix4 | ||
26 | , world :: [GameObject] | 28 | , world :: [GameObject] |
27 | } | 29 | } |
28 | 30 | ||
29 | app = App defaultAppOptions step render resize | 31 | type GameState = AppState Pong |
32 | |||
33 | |||
34 | options = defaultAppOptions { title = "Pong" } | ||
35 | |||
36 | app = App options initGame endGame step render resize | ||
37 | |||
30 | 38 | ||
31 | main = | 39 | main :: IO () |
32 | withWindow (1920, 1200) (Just "Pong") initGame endGame $ | 40 | main = runApp app |
33 | loop app | ||
34 | 41 | ||
35 | initGame :: Window -> Game () GameState | 42 | initGame :: Game AppContext Pong |
36 | initGame window = do | 43 | initGame = do |
37 | (immRenderState, renderCoreState) <- runSiblingGame newImmRenderer newRenderCoreState | 44 | music <- siblingGame $ do |
38 | return $ GameState window renderCoreState immRenderState Matrix4.id newWorld | 45 | musicBuffer <- loadAudioFile "/home/jeanne/Casual Tiki Party Main.wav" |
46 | music <- makeSoundSource | ||
47 | setSoundSourceBuffer music musicBuffer | ||
48 | setSoundLoopMode music Loop | ||
49 | playSounds [music] | ||
50 | return music | ||
51 | return $ Pong Matrix4.id music newWorld | ||
39 | 52 | ||
40 | endGame :: Game GameState () | 53 | endGame :: Game GameState () |
41 | endGame = do | 54 | endGame = return () |
42 | game <- getGameState | 55 | |
43 | runSubGame' (deleteImmRenderer $ immRenderState game) (renderCoreState game) | ||
44 | 56 | ||
45 | step :: Elapsed -> Dt -> [InputEvent] -> Game GameState Bool | 57 | step :: Elapsed -> Dt -> [InputEvent] -> Game GameState Bool |
46 | step elapsed dt inputEvents = do | 58 | step elapsed dt inputEvents = do |
47 | gs <- getGameState | 59 | appState <- get |
48 | events <- processInput (window gs) | 60 | gameState <- getGameState |
49 | --when (events /= []) $ gameIO . putStrLn $ show events | 61 | events <- processInput (appWindow appState) |
50 | modifyGameState $ \gs -> | 62 | --when (events /= []) $ liftIO . putStrLn $ show events |
51 | gs | 63 | modifyGameState $ \pong -> pong |
52 | { world = stepWorld (realToFrac elapsed) (realToFrac dt) events (world gs) | 64 | { world = stepWorld (realToFrac elapsed) (realToFrac dt) events (world gameState) |
53 | } | 65 | } |
54 | return (not $ exitRequested inputEvents) | 66 | return (not $ exitRequested inputEvents) |
55 | 67 | ||
56 | processInput :: Window -> Game GameState [GameEvent] | 68 | processInput :: Window -> Game GameState [GameEvent] |
@@ -61,20 +73,19 @@ processInput window = processKeys window | |||
61 | 73 | ||
62 | exitRequested = elem (KeyDown KEY_ESC) | 74 | exitRequested = elem (KeyDown KEY_ESC) |
63 | 75 | ||
76 | |||
64 | render :: Game GameState () | 77 | render :: Game GameState () |
65 | render = do | 78 | render = do |
66 | gameState <- getGameState | 79 | gameState <- getGameState |
67 | immRenderState' <- flip execSubGame (immRenderState gameState) $ do | 80 | siblingGame $ do |
68 | immStart | 81 | immStart |
69 | immSetViewProjectionMatrix (viewProjection gameState) | 82 | immSetViewProjectionMatrix (viewProjection gameState) |
70 | -- Clear the background to a different colour than the playable area to make | 83 | -- Clear the background to a different colour than the playable area to make |
71 | -- the latter distinguishable. | 84 | -- the latter distinguishable. |
72 | gameIO $ do | 85 | setClearColour (0.2, 0.2, 0.2, 0.0) |
73 | setClearColour (0.2, 0.2, 0.2, 0.0) | 86 | clearBuffers [ColourBuffer] |
74 | clearBuffers [ColourBuffer] | ||
75 | render' $ world gameState | 87 | render' $ world gameState |
76 | immEnd | 88 | immEnd |
77 | saveGameState $ gameState { immRenderState = immRenderState' } | ||
78 | 89 | ||
79 | render' :: [GameObject] -> Game ImmRenderState () | 90 | render' :: [GameObject] -> Game ImmRenderState () |
80 | render' world = do | 91 | render' world = do |
@@ -97,17 +108,16 @@ renderBackground = | |||
97 | ,vec2 pmin pmax)] | 108 | ,vec2 pmin pmax)] |
98 | 109 | ||
99 | renderGO :: GameObject -> Game ImmRenderState () | 110 | renderGO :: GameObject -> Game ImmRenderState () |
100 | renderGO go = do | 111 | renderGO go = |
101 | let (AABB2 (Vector2 xmin ymin) (Vector2 xmax ymax)) = aabb go | 112 | let (AABB2Volume (AABB2 (Vector2 xmin ymin) (Vector2 xmax ymax))) = boundingVolume go |
102 | (Vector2 xcenter ycenter) = position go | 113 | in |
103 | immPreservingMatrix $ do | ||
104 | immTranslate (vec3 xcenter ycenter 0) | ||
105 | immDrawQuads2d [ | 114 | immDrawQuads2d [ |
106 | (vec2 xmin ymin | 115 | (vec2 xmin ymin |
107 | ,vec2 xmax ymin | 116 | ,vec2 xmax ymin |
108 | ,vec2 xmax ymax | 117 | ,vec2 xmax ymax |
109 | ,vec2 xmin ymax)] | 118 | ,vec2 xmin ymax)] |
110 | 119 | ||
120 | |||
111 | resize :: WindowEvent -> Game GameState () | 121 | resize :: WindowEvent -> Game GameState () |
112 | resize (ResizeEvent w h) = | 122 | resize (ResizeEvent w h) = |
113 | let r = fromIntegral w / fromIntegral h | 123 | let r = fromIntegral w / fromIntegral h |
@@ -117,7 +127,7 @@ resize (ResizeEvent w h) = | |||
117 | bottom = if r > 1 then 0 else -pad | 127 | bottom = if r > 1 then 0 else -pad |
118 | top = if r > 1 then 1 else 1 + pad | 128 | top = if r > 1 then 1 else 1 + pad |
119 | in do | 129 | in do |
120 | gameIO $ setViewport 0 0 w h | 130 | setViewport 0 0 w h |
121 | modifyGameState $ \state -> state { | 131 | modifyGameState $ \pong -> pong { |
122 | viewProjection = Matrix4.ortho left right bottom top (-1) 1 | 132 | viewProjection = Matrix4.ortho left right bottom top (-1) 1 |
123 | } | 133 | } |
diff --git a/Demos/Pong/Pong.hs b/Demos/Pong/Pong.hs index b9661ee..0df05ea 100644 --- a/Demos/Pong/Pong.hs +++ b/Demos/Pong/Pong.hs | |||
@@ -3,12 +3,11 @@ | |||
3 | {-# LANGUAGE TypeSynonymInstances #-} | 3 | {-# LANGUAGE TypeSynonymInstances #-} |
4 | 4 | ||
5 | module Pong | 5 | module Pong |
6 | ( GameEvent (..), | 6 | ( GameEvent (..) |
7 | GameObject, | 7 | , GameObject |
8 | newWorld, | 8 | , newWorld |
9 | stepWorld, | 9 | , stepWorld |
10 | aabb, | 10 | ) |
11 | ) | ||
12 | where | 11 | where |
13 | 12 | ||
14 | import Spear.Math.AABB | 13 | import Spear.Math.AABB |
@@ -16,16 +15,17 @@ import Spear.Math.Algebra | |||
16 | import Spear.Math.Spatial | 15 | import Spear.Math.Spatial |
17 | import Spear.Math.Spatial2 | 16 | import Spear.Math.Spatial2 |
18 | import Spear.Math.Vector | 17 | import Spear.Math.Vector |
18 | import Spear.Physics.Collision | ||
19 | import Spear.Prelude | 19 | import Spear.Prelude |
20 | import Spear.Step | 20 | import Spear.Step |
21 | 21 | ||
22 | import Data.Monoid (mconcat) | 22 | import Data.Monoid (mconcat) |
23 | 23 | ||
24 | 24 | ||
25 | -- Configuration | 25 | -- Configuration |
26 | 26 | ||
27 | padSize = vec2 0.07 0.015 | 27 | padSize = vec2 0.070 0.015 |
28 | ballSize = 0.012 :: Float | 28 | ballSize = vec2 0.012 0.012 |
29 | ballSpeed = 0.7 :: Float | 29 | ballSpeed = 0.7 :: Float |
30 | initialBallVelocity = vec2 1 1 | 30 | initialBallVelocity = vec2 1 1 |
31 | maxBounceAngle = (65::Float) * (pi::Float)/(180::Float) | 31 | maxBounceAngle = (65::Float) * (pi::Float)/(180::Float) |
@@ -41,14 +41,22 @@ initialBallPos = vec2 0.5 0.5 | |||
41 | data GameEvent | 41 | data GameEvent |
42 | = MoveLeft | 42 | = MoveLeft |
43 | | MoveRight | 43 | | MoveRight |
44 | deriving (Eq, Ord, Show) | 44 | | Collision GameObjectId GameObjectId |
45 | deriving (Eq, Show) | ||
45 | 46 | ||
46 | -- Game objects | 47 | -- Game objects |
47 | 48 | ||
49 | data GameObjectId | ||
50 | = Ball | ||
51 | | Enemy | ||
52 | | Player | ||
53 | deriving (Eq, Show) | ||
54 | |||
48 | data GameObject = GameObject | 55 | data GameObject = GameObject |
49 | { aabb :: AABB2, | 56 | { gameObjectId :: !GameObjectId |
50 | basis :: Transform2, | 57 | , gameObjectSize :: {-# UNPACK #-} !Vector2 |
51 | gostep :: Step [GameObject] [GameEvent] GameObject GameObject | 58 | , basis :: {-# UNPACK #-} !Transform2 |
59 | , gostep :: Step [GameObject] [GameEvent] GameObject GameObject | ||
52 | } | 60 | } |
53 | 61 | ||
54 | 62 | ||
@@ -78,76 +86,83 @@ instance Spatial GameObject Vector2 Angle Transform2 where | |||
78 | transform = basis | 86 | transform = basis |
79 | 87 | ||
80 | 88 | ||
81 | ballBox, padBox :: AABB2 | 89 | instance Bounded2 GameObject where |
82 | ballBox = AABB2 (vec2 (-s) (-s)) (vec2 s s) where s = ballSize | 90 | boundingVolume obj = aabb2Volume $ translate (position obj) (AABB2 (-size) size) |
83 | padBox = AABB2 (-padSize) padSize | 91 | where size = gameObjectSize obj |
92 | |||
84 | 93 | ||
85 | newWorld = | 94 | newWorld = |
86 | [ GameObject ballBox (makeAt initialBallPos) $ stepBall initialBallVelocity, | 95 | [ GameObject Ball ballSize (makeAt initialBallPos) $ stepBall initialBallVelocity, |
87 | GameObject padBox (makeAt initialEnemyPos) stepEnemy, | 96 | GameObject Enemy padSize (makeAt initialEnemyPos) stepEnemy, |
88 | GameObject padBox (makeAt initialPlayerPos) stepPlayer | 97 | GameObject Player padSize (makeAt initialPlayerPos) stepPlayer |
89 | ] | 98 | ] |
90 | where makeAt = newTransform2 unitx2 unity2 | 99 | where makeAt = newTransform2 unitx2 unity2 |
91 | 100 | ||
92 | 101 | ||
102 | -- Step the game world: | ||
103 | -- 1. Simulate physics. | ||
104 | -- 2. Collide objects and clip -> produce collision events. | ||
105 | -- 3. Update game objects <- input collision events. | ||
93 | stepWorld :: Elapsed -> Dt -> [GameEvent] -> [GameObject] -> [GameObject] | 106 | stepWorld :: Elapsed -> Dt -> [GameEvent] -> [GameObject] -> [GameObject] |
94 | stepWorld elapsed dt evts gos = map (update elapsed dt evts gos) gos | 107 | stepWorld elapsed dt events gos@[ball, enemy, player] = |
108 | let | ||
109 | collisions = collide [ball] [enemy, player] | ||
110 | collisionEvents = (\(x,y) -> Collision (gameObjectId x) (gameObjectId y)) <$> collisions | ||
111 | events' = events ++ collisionEvents | ||
112 | in | ||
113 | map (update elapsed dt events' gos) gos | ||
95 | 114 | ||
96 | update :: Elapsed -> Dt -> [GameEvent] -> [GameObject] -> GameObject -> GameObject | 115 | update :: Elapsed -> Dt -> [GameEvent] -> [GameObject] -> GameObject -> GameObject |
97 | update elapsed dt evts gos go = | 116 | update elapsed dt events gos go = |
98 | let (go', s') = runStep (gostep go) elapsed dt gos evts go | 117 | let (go', s') = runStep (gostep go) elapsed dt gos events go |
99 | in go' {gostep = s'} | 118 | in go' { gostep = s' } |
119 | |||
100 | 120 | ||
101 | -- Ball steppers | 121 | -- Ball steppers |
102 | 122 | ||
103 | stepBall vel = collideBall vel .> moveBall | 123 | stepBall vel = bounceBall vel .> moveBall -- .> clamp |
104 | 124 | ||
105 | collideBall :: Vector2 -> Step [GameObject] e GameObject (Vector2, GameObject) | 125 | bounceBall :: Vector2 -> Step [GameObject] [GameEvent] GameObject (Vector2, GameObject) |
106 | collideBall vel = step $ \_ dt gos _ ball -> | 126 | bounceBall vel = step $ \_ dt gos events ball -> |
107 | let (AABB2 pmin pmax) = translate (position ball) (aabb ball) | 127 | let (AABB2Volume (AABB2 pmin pmax)) = boundingVolume ball |
108 | sideCollision = x pmin < 0 || x pmax > 1 | 128 | sideCollision = x pmin < 0 || x pmax > 1 |
109 | backCollision = y pmin < 0 || y pmax > 1 | 129 | backCollision = y pmin < 0 || y pmax > 1 |
110 | flipX v@(Vector2 x y) = if sideCollision then vec2 (-x) y else v | 130 | flipX v@(Vector2 x y) = if sideCollision then vec2 (-x) y else v |
111 | flipY v@(Vector2 x y) = if backCollision then vec2 x (-y) else v | 131 | flipY v@(Vector2 x y) = if backCollision then vec2 x (-y) else v |
112 | vel' = normalise . (\v -> foldl (paddleBounce ball) v (tail gos)) . flipX . flipY $ vel | 132 | collideWithPaddles vel = foldl (paddleBounce ball events) vel (tail gos) |
133 | vel' = normalise | ||
134 | . collideWithPaddles | ||
135 | . flipX | ||
136 | . flipY | ||
137 | $ vel | ||
113 | collision = vel' /= vel | 138 | collision = vel' /= vel |
114 | -- Apply offset when collision occurs to avoid sticky collisions. | 139 | -- Apply offset when collision occurs to avoid sticky collisions. |
115 | delta = (1::Float) + if collision then (3::Float)*dt else (0::Float) | 140 | delta = (1::Float) + if collision then (3::Float)*dt else (0::Float) |
116 | in ((ballSpeed * delta * vel', ball), collideBall vel') | 141 | in ((ballSpeed * delta * vel', ball), bounceBall vel') |
117 | 142 | ||
118 | paddleBounce :: GameObject -> Vector2 -> GameObject -> Vector2 | 143 | paddleBounce :: GameObject -> [GameEvent] -> Vector2 -> GameObject -> Vector2 |
119 | paddleBounce ball v paddle = | 144 | paddleBounce ball events vel paddle = |
120 | if collide ball paddle | 145 | let collision = Collision Ball (gameObjectId paddle) `elem` events |
146 | in if collision | ||
121 | then | 147 | then |
122 | let (AABB2 pmin pmax) = translate (position paddle) (aabb paddle) | 148 | let (AABB2Volume (AABB2 pmin pmax)) = boundingVolume paddle |
123 | center = (x pmin + x pmax) / (2::Float) | 149 | center = (x pmin + x pmax) / (2::Float) |
124 | -- Normalized offset of the ball from the paddle's center, [-1, +1]. | 150 | -- Normalized offset of the ball from the paddle's center, [-1, +1]. |
125 | -- It's outside the [-1, +1] range if there is no collision. | 151 | -- It's outside the [-1, +1] range if there is no collision. |
126 | offset = (x (position ball) - center) / ((x pmax - x pmin) / (2::Float)) | 152 | offset = (x (position ball) - center) / ((x pmax - x pmin) / (2::Float)) |
127 | angle = offset * maxBounceAngle | 153 | angle = offset * maxBounceAngle |
128 | -- When it bounces off of a paddle, y vel is flipped. | 154 | -- When it bounces off of a paddle, y vel is flipped. |
129 | ysign = -(signum (y v)) | 155 | ysign = -(signum (y vel)) |
130 | in vec2 (sin angle) (ysign * cos angle) | 156 | in vec2 (sin angle) (ysign * cos angle) |
131 | else v | 157 | else vel |
132 | |||
133 | collide :: GameObject -> GameObject -> Bool | ||
134 | collide go1 go2 = | ||
135 | let (AABB2 (Vector2 xmin1 ymin1) (Vector2 xmax1 ymax1)) = | ||
136 | translate (position go1) (aabb go1) | ||
137 | (AABB2 (Vector2 xmin2 ymin2) (Vector2 xmax2 ymax2)) = | ||
138 | translate (position go2) (aabb go2) | ||
139 | in not $ | ||
140 | xmax1 < xmin2 || | ||
141 | xmin1 > xmax2 || | ||
142 | ymax1 < ymin2 || | ||
143 | ymin1 > ymax2 | ||
144 | 158 | ||
145 | moveBall :: Step s e (Vector2, GameObject) GameObject | 159 | moveBall :: Step s e (Vector2, GameObject) GameObject |
146 | moveBall = step $ \_ dt _ _ (vel, ball) -> (translate (vel * dt) ball, moveBall) | 160 | moveBall = step $ \_ dt _ _ (vel, ball) -> (translate (vel * dt) ball, moveBall) |
147 | 161 | ||
162 | |||
148 | -- Enemy stepper | 163 | -- Enemy stepper |
149 | 164 | ||
150 | stepEnemy = movePad 0 .> clamp | 165 | stepEnemy = movePad 0 .> spure clamp |
151 | 166 | ||
152 | movePad :: Float -> Step [GameObject] e GameObject GameObject | 167 | movePad :: Float -> Step [GameObject] e GameObject GameObject |
153 | movePad previousMomentumVector = step $ \_ dt gos _ pad -> | 168 | movePad previousMomentumVector = step $ \_ dt gos _ pad -> |
@@ -158,28 +173,26 @@ movePad previousMomentumVector = step $ \_ dt gos _ pad -> | |||
158 | vx = chaseVector * dt + momentumVector | 173 | vx = chaseVector * dt + momentumVector |
159 | in (translate (vec2 vx 0) pad, movePad momentumVector) | 174 | in (translate (vec2 vx 0) pad, movePad momentumVector) |
160 | 175 | ||
161 | sign :: Float -> Float | ||
162 | sign x = if x >= 0 then 1 else -1 | ||
163 | 176 | ||
164 | -- Player stepper | 177 | -- Player stepper |
165 | 178 | ||
166 | stepPlayer = sfold moveGO .> clamp | 179 | stepPlayer = sfold movePlayer .> spure clamp |
167 | 180 | ||
168 | moveGO = mconcat | 181 | movePlayer = mconcat |
169 | [ swhen MoveLeft $ moveGO' (vec2 (-playerSpeed) 0) | 182 | [ swhen MoveLeft $ movePlayer' (vec2 (-playerSpeed) 0) |
170 | , swhen MoveRight $ moveGO' (vec2 playerSpeed 0) | 183 | , swhen MoveRight $ movePlayer' (vec2 playerSpeed 0) |
171 | ] | 184 | ] |
172 | 185 | ||
173 | moveGO' :: Vector2 -> Step s e GameObject GameObject | 186 | movePlayer' :: Vector2 -> Step s e GameObject GameObject |
174 | moveGO' dir = step $ \_ dt _ _ go -> (translate (dir * dt) go, moveGO' dir) | 187 | movePlayer' dir = step $ \_ dt _ _ go -> (translate (dir * dt) go, movePlayer' dir) |
175 | 188 | ||
176 | clamp :: Step s e GameObject GameObject | 189 | clamp :: GameObject -> GameObject |
177 | clamp = spure $ \go -> | 190 | clamp go = |
178 | let p' = vec2 (clamp' x s (1 - s)) y | 191 | let p' = vec2 (clamp' x sx (1 - sx)) y |
179 | (Vector2 x y) = position go | 192 | (Vector2 x y) = position go |
180 | clamp' x a b | 193 | clamp' x a b |
181 | | x < a = a | 194 | | x < a = a |
182 | | x > b = b | 195 | | x > b = b |
183 | | otherwise = x | 196 | | otherwise = x |
184 | (Vector2 s _) = padSize | 197 | (Vector2 sx _) = gameObjectSize go |
185 | in setPosition p' go | 198 | in setPosition p' go |