aboutsummaryrefslogtreecommitdiff
path: root/Demos
diff options
context:
space:
mode:
author3gg <3gg@shellblade.net>2024-12-30 20:59:27 -0800
committer3gg <3gg@shellblade.net>2024-12-30 20:59:27 -0800
commite2b76464e847e5c656e6adf6d8e07a054756cda0 (patch)
treea38fe19bc4086e34b59e56e84550725794b2736a /Demos
parentf1939232bec72fffede16a55119bc7c4fb3057cf (diff)
Use bounding volume in other places.
Diffstat (limited to 'Demos')
-rw-r--r--Demos/Pong/Main.hs9
-rw-r--r--Demos/Pong/Pong.hs40
2 files changed, 22 insertions, 27 deletions
diff --git a/Demos/Pong/Main.hs b/Demos/Pong/Main.hs
index df90020..b93325d 100644
--- a/Demos/Pong/Main.hs
+++ b/Demos/Pong/Main.hs
@@ -9,6 +9,7 @@ import Spear.Math.Matrix4 as Matrix4 hiding (position)
9import Spear.Math.Spatial 9import Spear.Math.Spatial
10import Spear.Math.Spatial2 10import Spear.Math.Spatial2
11import Spear.Math.Vector 11import Spear.Math.Vector
12import Spear.Physics.Collision
12import Spear.Render.Core.Pipeline 13import Spear.Render.Core.Pipeline
13import Spear.Render.Core.State 14import Spear.Render.Core.State
14import Spear.Render.Immediate 15import Spear.Render.Immediate
@@ -101,11 +102,9 @@ renderBackground =
101 ,vec2 pmin pmax)] 102 ,vec2 pmin pmax)]
102 103
103renderGO :: GameObject -> Game ImmRenderState () 104renderGO :: GameObject -> Game ImmRenderState ()
104renderGO go = do 105renderGO go =
105 let (AABB2 (Vector2 xmin ymin) (Vector2 xmax ymax)) = aabb go 106 let (AABB2Volume (AABB2 (Vector2 xmin ymin) (Vector2 xmax ymax))) = boundingVolume go
106 (Vector2 xcenter ycenter) = position go 107 in
107 immPreservingMatrix $ do
108 immTranslate (vec3 xcenter ycenter 0)
109 immDrawQuads2d [ 108 immDrawQuads2d [
110 (vec2 xmin ymin 109 (vec2 xmin ymin
111 ,vec2 xmax ymin 110 ,vec2 xmax ymin
diff --git a/Demos/Pong/Pong.hs b/Demos/Pong/Pong.hs
index b12f792..790a98e 100644
--- a/Demos/Pong/Pong.hs
+++ b/Demos/Pong/Pong.hs
@@ -3,12 +3,11 @@
3{-# LANGUAGE TypeSynonymInstances #-} 3{-# LANGUAGE TypeSynonymInstances #-}
4 4
5module Pong 5module Pong
6 ( GameEvent (..), 6( GameEvent (..)
7 GameObject, 7, GameObject
8 newWorld, 8, newWorld
9 stepWorld, 9, stepWorld
10 aabb, 10)
11 )
12where 11where
13 12
14import Spear.Math.AABB 13import Spear.Math.AABB
@@ -25,8 +24,8 @@ import Data.Monoid (mconcat)
25 24
26-- Configuration 25-- Configuration
27 26
28padSize = vec2 0.07 0.015 27padSize = vec2 0.070 0.015
29ballSize = 0.012 :: Float 28ballSize = vec2 0.012 0.012
30ballSpeed = 0.7 :: Float 29ballSpeed = 0.7 :: Float
31initialBallVelocity = vec2 1 1 30initialBallVelocity = vec2 1 1
32maxBounceAngle = (65::Float) * (pi::Float)/(180::Float) 31maxBounceAngle = (65::Float) * (pi::Float)/(180::Float)
@@ -54,10 +53,10 @@ data GameObjectId
54 deriving (Eq, Show) 53 deriving (Eq, Show)
55 54
56data GameObject = GameObject 55data GameObject = GameObject
57 { gameObjectId :: !GameObjectId 56 { gameObjectId :: !GameObjectId
58 , aabb :: {-# UNPACK #-} !AABB2 57 , gameObjectSize :: {-# UNPACK #-} !Vector2
59 , basis :: {-# UNPACK #-} !Transform2 58 , basis :: {-# UNPACK #-} !Transform2
60 , gostep :: Step [GameObject] [GameEvent] GameObject GameObject 59 , gostep :: Step [GameObject] [GameEvent] GameObject GameObject
61 } 60 }
62 61
63 62
@@ -88,17 +87,14 @@ instance Spatial GameObject Vector2 Angle Transform2 where
88 87
89 88
90instance Bounded2 GameObject where 89instance Bounded2 GameObject where
91 boundingVolume obj = aabb2Volume $ translate (position obj) (aabb obj) 90 boundingVolume obj = aabb2Volume $ translate (position obj) (AABB2 (-size) size)
91 where size = gameObjectSize obj
92 92
93 93
94ballBox, padBox :: AABB2
95ballBox = AABB2 (vec2 (-s) (-s)) (vec2 s s) where s = ballSize
96padBox = AABB2 (-padSize) padSize
97
98newWorld = 94newWorld =
99 [ GameObject Ball ballBox (makeAt initialBallPos) $ stepBall initialBallVelocity, 95 [ GameObject Ball ballSize (makeAt initialBallPos) $ stepBall initialBallVelocity,
100 GameObject Enemy padBox (makeAt initialEnemyPos) stepEnemy, 96 GameObject Enemy padSize (makeAt initialEnemyPos) stepEnemy,
101 GameObject Player padBox (makeAt initialPlayerPos) stepPlayer 97 GameObject Player padSize (makeAt initialPlayerPos) stepPlayer
102 ] 98 ]
103 where makeAt = newTransform2 unitx2 unity2 99 where makeAt = newTransform2 unitx2 unity2
104 100
@@ -129,7 +125,7 @@ stepBall vel = bounceBall vel .> moveBall
129 125
130bounceBall :: Vector2 -> Step [GameObject] [GameEvent] GameObject (Vector2, GameObject) 126bounceBall :: Vector2 -> Step [GameObject] [GameEvent] GameObject (Vector2, GameObject)
131bounceBall vel = step $ \_ dt gos events ball -> 127bounceBall vel = step $ \_ dt gos events ball ->
132 let (AABB2 pmin pmax) = translate (position ball) (aabb ball) 128 let (AABB2Volume (AABB2 pmin pmax)) = boundingVolume ball
133 sideCollision = x pmin < 0 || x pmax > 1 129 sideCollision = x pmin < 0 || x pmax > 1
134 backCollision = y pmin < 0 || y pmax > 1 130 backCollision = y pmin < 0 || y pmax > 1
135 flipX v@(Vector2 x y) = if sideCollision then vec2 (-x) y else v 131 flipX v@(Vector2 x y) = if sideCollision then vec2 (-x) y else v
@@ -150,7 +146,7 @@ paddleBounce ball events vel paddle =
150 let collision = Collision Ball (gameObjectId paddle) `elem` events 146 let collision = Collision Ball (gameObjectId paddle) `elem` events
151 in if collision 147 in if collision
152 then 148 then
153 let (AABB2 pmin pmax) = translate (position paddle) (aabb paddle) 149 let (AABB2Volume (AABB2 pmin pmax)) = boundingVolume paddle
154 center = (x pmin + x pmax) / (2::Float) 150 center = (x pmin + x pmax) / (2::Float)
155 -- Normalized offset of the ball from the paddle's center, [-1, +1]. 151 -- Normalized offset of the ball from the paddle's center, [-1, +1].
156 -- It's outside the [-1, +1] range if there is no collision. 152 -- It's outside the [-1, +1] range if there is no collision.