aboutsummaryrefslogtreecommitdiff
path: root/Demos/Balls
diff options
context:
space:
mode:
Diffstat (limited to 'Demos/Balls')
-rw-r--r--Demos/Balls/Main.hs177
1 files changed, 177 insertions, 0 deletions
diff --git a/Demos/Balls/Main.hs b/Demos/Balls/Main.hs
new file mode 100644
index 0000000..2e759bc
--- /dev/null
+++ b/Demos/Balls/Main.hs
@@ -0,0 +1,177 @@
1{-# LANGUAGE MultiParamTypeClasses #-}
2--{-# LANGUAGE NoImplicitPrelude #-}
3{-# LANGUAGE FlexibleContexts #-}
4{-# LANGUAGE TypeSynonymInstances #-}
5
6module Main where
7
8import Spear.App
9import Spear.Game
10import Spear.Math.AABB
11import qualified Spear.Math.Matrix3 as Matrix3
12import qualified Spear.Math.Matrix4 as Matrix4
13import Spear.Math.Spatial
14import Spear.Math.Spatial2
15import Spear.Math.Vector
16import Spear.Physics.Collision
17--import Spear.Prelude
18import Spear.Render.Core.Pipeline
19import Spear.Render.Core.State
20import Spear.Render.Immediate
21import Spear.Sound.Sound
22import Spear.Sound.State
23import Spear.Window
24
25import Control.Monad (when)
26import Spear.Math.Vector (Vector3)
27
28
29ballSize = 0.01
30numBalls = 1000
31
32data Ball = Ball
33 { ballPosition :: {-# UNPACK #-} !Vector2
34 , ballVelocity :: {-# UNPACK #-} !Vector2
35 }
36
37instance Positional Ball Vector2 where
38 setPosition p ball = ball { ballPosition = p }
39 position = ballPosition
40 translate v ball = ball { ballPosition = v + ballPosition ball }
41
42instance Bounded2 Ball where
43 boundingVolume ball = aabb2Volume $ translate (ballPosition ball) (AABB2 (-size) size)
44 where size = vec2 s s
45 s = ballSize / (2::Float)
46
47data World = World
48 { viewProjection :: Matrix4.Matrix4
49 , balls :: [Ball]
50 }
51
52type GameState = AppState World
53
54
55options = defaultAppOptions { title = "Balls" }
56
57app = App options initGame endGame step render resize
58
59
60main :: IO ()
61main = runApp app
62
63initGame :: Game AppContext World
64initGame =
65 let
66 world = zipWith Ball positions velocities
67 positions = (+vec2 0.5 0.5) . makePosition <$> numbers
68 makePosition i = radius * vec2 (sin (f*i)) (cos (f*i))
69 velocities = makeVelocity <$> numbers
70 makeVelocity i = scale speed $ vec2 (sin (f*i)) (cos (f*i))
71 numbers = [1..numBalls]
72 f = 2*pi / numBalls
73 radius = 0.05
74 speed = 0.4
75 in
76 return $ World Matrix4.id world
77
78endGame :: Game GameState ()
79endGame = return ()
80
81
82step :: Elapsed -> Dt -> [InputEvent] -> Game GameState Bool
83step elapsed dt inputEvents = do
84 modifyGameState $ \world -> world
85 { balls = moveBalls dt $ balls world
86 }
87 return (not $ exitRequested inputEvents)
88
89exitRequested = elem (KeyDown KEY_ESC)
90
91moveBalls :: Elapsed -> [Ball] -> [Ball]
92moveBalls dt = (bounceBall dt . moveBall dt <$>)
93
94moveBall :: Elapsed -> Ball -> Ball
95moveBall dt ball = translate (scale (realToFrac dt) $ ballVelocity ball) ball
96
97bounceBall :: Elapsed -> Ball -> Ball
98bounceBall dt ball =
99 let
100 (AABB2Volume (AABB2 pmin pmax)) = boundingVolume ball
101 sideCollision = x pmin < 0 || x pmax > 1
102 backCollision = y pmin < 0 || y pmax > 1
103 flipX v@(Vector2 x y) = if sideCollision then vec2 (-x) y else v
104 flipY v@(Vector2 x y) = if backCollision then vec2 x (-y) else v
105 velocity = ballVelocity ball
106 velocity'
107 = flipX
108 . flipY
109 $ velocity
110 collision = velocity' /= velocity
111 -- Apply offset when collision occurs to avoid sticky collisions.
112 delta = if collision then 1 else 0
113 dt' = realToFrac dt
114 in
115 ball
116 { ballPosition = ballPosition ball + scale (delta * dt') velocity'
117 , ballVelocity = velocity'
118 }
119
120
121render :: Game GameState ()
122render = do
123 gameState <- getGameState
124 siblingGame $ do
125 immStart
126 immSetViewProjectionMatrix (viewProjection gameState)
127 -- Clear the background to a different colour than the playable area to make
128 -- the latter distinguishable.
129 setClearColour (0.2, 0.2, 0.2, 0.0)
130 clearBuffers [ColourBuffer]
131 render' $ balls gameState
132 immEnd
133
134render' :: [Ball] -> Game ImmRenderState ()
135render' balls = do
136 immLoadIdentity
137 renderBackground
138 -- Draw objects.
139 immSetColour (vec4 1.0 1.0 1.0 1.0)
140 mapM_ renderBall balls
141
142renderBackground :: Game ImmRenderState ()
143renderBackground =
144 let pmin = 0 :: Float
145 pmax = 1 :: Float
146 in do
147 immSetColour (vec4 0.0 0.25 0.41 1.0)
148 immDrawQuads2d [
149 (vec2 pmin pmin
150 ,vec2 pmax pmin
151 ,vec2 pmax pmax
152 ,vec2 pmin pmax)]
153
154renderBall :: Ball -> Game ImmRenderState ()
155renderBall ball =
156 let (AABB2Volume (AABB2 (Vector2 xmin ymin) (Vector2 xmax ymax))) = boundingVolume ball
157 in
158 immDrawQuads2d [
159 (vec2 xmin ymin
160 ,vec2 xmax ymin
161 ,vec2 xmax ymax
162 ,vec2 xmin ymax)]
163
164
165resize :: WindowEvent -> Game GameState ()
166resize (ResizeEvent w h) =
167 let r = fromIntegral w / fromIntegral h
168 pad = if r > 1 then (r-1) / 2 else (1/r - 1) / 2
169 left = if r > 1 then -pad else 0
170 right = if r > 1 then 1 + pad else 1
171 bottom = if r > 1 then 0 else -pad
172 top = if r > 1 then 1 else 1 + pad
173 in do
174 setViewport 0 0 w h
175 modifyGameState $ \pong -> pong {
176 viewProjection = Matrix4.ortho left right bottom top (-1) 1
177 }