Fleshed out some of the functions and performed some refactoring. Note that there...
authorsabadev <saba@sabadev.xyz>
Sat, 30 Jan 2021 23:05:39 +0000 (18:05 -0500)
committersabadev <saba@sabadev.xyz>
Sun, 31 Jan 2021 14:03:56 +0000 (09:03 -0500)
src/Game.hs

index b2818ed..9eb386e 100644 (file)
@@ -1,18 +1,19 @@
 module Game where
 
+import Data.Bifunctor (bimap)
 import qualified Terminal.Game as G
 
-newtype Vector = Vector { getVector :: (G.Row, G.Column) } deriving (Eq)
+newtype Velocity = Velocity { getVelocity :: (G.Row, G.Column) } deriving (Eq)
 
-instance Semigroup Vector where
-  (Vector (x1, y1)) <> (Vector (x2, y2)) = Vector $ (addLimit x1 x2, addLimit y1 y2) where
+instance Semigroup Velocity where
+  (Velocity (x1, y1)) <> (Velocity (x2, y2)) = Velocity $ (addLimit x1 x2, addLimit y1 y2) where
     addLimit a b
       | a + b > 1 = 1
       | a + b < -1 = -1
       | otherwise = a + b
 
-instance Monoid Vector where
-  mempty = Vector (0, 0)
+instance Monoid Velocity where
+  mempty = Velocity (0, 0)
 
 data Direction = U | D | L | R deriving (Eq)
 
@@ -21,7 +22,7 @@ data Box
 data Enemy
 
 data Character t = Character { entityCoords :: !G.Coords
-                             , entityVector :: !Vector
+                             , entityVelocity :: !Velocity
                              }
 
 drawPlayer :: Character Player -> G.Plane
@@ -38,23 +39,39 @@ data State = State { stateDirection :: ![Direction]
                    , stateBox :: !(Character Box)
                    , stateEnemy :: ![Character Enemy]
                    , stateIsQuitting :: !Bool
+                   , stateRandomGen :: !G.StdGen
                    }
 
-boundaries :: (G.Coords, G.Coords)
-boundaries = ((1, 1), (24, 80))
+gameSettings :: G.StdGen -> G.Game State
+gameSettings stdgen = G.Game { G.gScreenWidth = fst bottomRightBoundary
+                             , G.gScreenHeight = snd bottomRightBoundary
+                             , G.gFPS = 15
+                             , G.gInitState = initState stdgen
+                             , G.gLogicFunction = handleEvent
+                             , G.gDrawFunction = render
+                             , G.gQuitFunction = shouldQuit
+                             }
+
+initState :: G.StdGen -> State
+initState stdgen = State { stateDirection = []
+                         , statePlayer = initPlayer
+                         , stateBox = initBox
+                         , stateEnemy = initEnemies
+                         , stateIsQuitting = False
+                         , stateRandomGen = stdgen
+                         }
+
+centreCoords :: G.Coords
+centreCoords = bimap (+ fst topLeftBoundary) (+ snd topLeftBoundary) $ fmap (flip div 2) (fst bottomRightBoundary - fst topLeftBoundary, snd bottomRightBoundary - snd topLeftBoundary)
 
-gameSettings :: G.Game State
-gameSettings = G.Game { G.gScreenWidth = fst $ snd boundaries
-                      , G.gScreenHeight = snd $ snd boundaries
-                      , G.gFPS = 15
-                      , G.gInitState = initState
-                      , G.gLogicFunction = handleEvent
-                      , G.gDrawFunction = render
-                      , G.gQuitFunction = shouldQuit
-                      }
+initPlayer :: Character Player
+initPlayer = Character { entityCoords = centreCoords, entityVelocity = mempty }
 
-initState :: State
-initState = undefined
+initBox :: Character Box
+initBox = Character { entityCoords = limitCoords $ bimap (+ 1) (+ 1) centreCoords, entityVelocity = mempty }
+
+initEnemies :: [Character Enemy]
+initEnemies = mempty
 
 handleEvent :: State -> G.Event -> State
 handleEvent = undefined
@@ -63,10 +80,39 @@ render :: State -> G.Plane
 render = undefined
 
 shouldQuit :: State -> Bool
-shouldQuit = undefined
+shouldQuit = stateIsQuitting
+
+boundaries :: (G.Coords, G.Coords)
+boundaries = ((1, 1), (24, 80))
 
-directionToVector :: Direction -> Vector
-directionToVector U = Vector (0, -1)
-directionToVector D = Vector (0, 1)
-directionToVector L = Vector (-1, 0)
-directionToVector R = Vector (1, 0)
+topLeftBoundary :: G.Coords
+topLeftBoundary = fst boundaries
+
+bottomRightBoundary :: G.Coords
+bottomRightBoundary = snd boundaries
+
+directionToVelocity :: Direction -> Velocity
+directionToVelocity U = Velocity (0, -1)
+directionToVelocity D = Velocity (0, 1)
+directionToVelocity L = Velocity (-1, 0)
+directionToVelocity R = Velocity (1, 0)
+
+limitCoords :: G.Coords -> G.Coords
+limitCoords (a, b) = (limitRowCoord a, limitColumnCoord b)
+  where
+    limitRowCoord a
+      | a < fst topLeftBoundary = fst topLeftBoundary
+      | a > fst bottomRightBoundary = fst bottomRightBoundary
+      | otherwise = a
+    limitColumnCoord a
+      | a < snd topLeftBoundary = snd topLeftBoundary
+      | a > snd bottomRightBoundary = snd bottomRightBoundary
+      | otherwise = a
+
+updatePosition :: Character t -> Character t
+updatePosition character = do
+  let Velocity (velocityX, velocityY) = entityVelocity character
+  let (oldRow, oldColumn) = entityCoords character
+  let newCoords = (oldRow + velocityX, oldColumn + velocityY)
+  let boundedCoords = limitCoords newCoords
+  character { entityCoords = boundedCoords }