Skip to content

Commit

Permalink
[Broken] Started work on entities
Browse files Browse the repository at this point in the history
- Entities are going to replace 'Guy', and are the fundamental structure to a game
- The entities list inside the game state will need to contain every object in the game, therefore there needs to be multiple data constructors to allow different types of Entities to be made (Similar to Bool being True or False, and Entity will be a dynamic entity such as a character or a static object to be rendered
- Build is currently broken
  • Loading branch information
Ashe committed Mar 30, 2018
1 parent 1f774fb commit 6bef3ef
Show file tree
Hide file tree
Showing 5 changed files with 79 additions and 59 deletions.
1 change: 1 addition & 0 deletions FirstGameHS.cabal
Expand Up @@ -31,6 +31,7 @@ executable FirstGameHS
, bytestring
other-modules: Paths_FirstGameHS
, GameState
, Entity
, SDLAnimations
, AnimationLoader
, InputModule
43 changes: 43 additions & 0 deletions src/Entity.hs
@@ -0,0 +1,43 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PatternSynonyms #-}
module Entity
( Entity(Entity)
, position
, velocity
, tag
, animation
, frame
) where

import Control.Monad
import Foreign.C.Types
import SDL.Vect
import SDL (($=))
import qualified SDL
import qualified SDL.Image
import Data.List (foldl')
import SDL.Raw.Timer as SDL hiding (delay)
import Text.Pretty.Simple

-- The fundamental structures of all our objects in the game
data Entity =
Entity
{ position :: Point V2 CDouble
, velocity :: V2 CDouble
, tag :: String
, animation :: String
, frame :: Int
} deriving (Show, Eq)


-- Our initial guy starts out with him roughly in the middle
initialGuy :: (CDouble, CDouble) -> Entity
initialGuy pos =
Entity
{ position = P $ V2 (fst pos) (snd pos)
, velocity = V2 0 0
, tag = "male"
, animation = "idle"
, frame = 0
}

58 changes: 17 additions & 41 deletions src/GameState.hs
@@ -1,32 +1,30 @@
module GameState ( GameState(State)
, Guy(Guy)
, Options(Options)
, KeyBindings
, initialState
, entities
, position
, velocity
, options
, initialOptions
, screenRes
, frameLimit
, keybindings
, processInput
)
where
module GameState
( GameState(State)
, Options(Options)
, KeyBindings
, initialState
, entities
, options
, initialOptions
, screenRes
, frameLimit
, keybindings
, processInput
) where

import Control.Monad
import Foreign.C.Types
import SDL
import qualified SDL

import InputModule
import Entity

-- Hands the current state of the game to various functions
data GameState =
State
{ options :: Options
, entities :: Guy
, entities :: [Entity]
}

-- We will need this later so just making a newtype for now
Expand All @@ -37,35 +35,13 @@ data Options =
, keybindings :: KeyBindings GameState
}

-- This is our game world. It only consists of one lonely guy
-- who has a position and a velocity
data Guy =
Guy
{ position :: Point V2 CDouble
, velocity :: V2 CDouble
, tag :: String
, animation :: String
, frame :: Int
} deriving (Show, Eq)

initialState :: GameState
initialState = State initialOptions (initialGuy initialOptions)

-- Our initial guy starts out with him roughly in the middle
initialGuy :: Options -> Guy
initialGuy opts =
Guy
{ position = P $ V2 (fromIntegral (fst (screenRes opts)) / 2) (fromIntegral $ snd (screenRes opts) - 100)
, velocity = V2 0 0
, tag = "male"
, animation = "idle"
, frame = 0
}
initialState = State initialOptions []

initialOptions :: Options
initialOptions =
Options
{ screenRes = (640, 480)
{ screenRes = (1440, 1080)
, frameLimit = 60
, keybindings = blankKeyBindings :: KeyBindings GameState
}
Expand Down
15 changes: 7 additions & 8 deletions src/InputModule.hs
@@ -1,12 +1,12 @@
-- This module is responsible for handling input flexibly

module InputModule ( KeyBindings(KeyBindings)
, addBinding
, addBatchBindings
, getBoundInput
, blankKeyBindings
)
where
module InputModule
( KeyBindings(KeyBindings)
, addBinding
, addBatchBindings
, getBoundInput
, blankKeyBindings
) where

import Control.Monad
import Foreign.C.Types
Expand All @@ -16,7 +16,6 @@ import qualified SDL
import qualified Data.Map as Map

-- State for keeping track of animations
-- newtype KeyBindings state = KeyBindings [(SDL.Keycode, Maybe (state -> state))]
newtype KeyBindings state = KeyBindings (Map.Map (SDL.Keycode, Bool) (Maybe (state -> state)))

-- Blank keybindings map
Expand Down
21 changes: 11 additions & 10 deletions src/SDLAnimations.hs
@@ -1,15 +1,16 @@
-- This module is responsible for taking animationData and applying it into an SDL context

module SDLAnimations ( AnimationSet()
, Animation()
, AnimationState(AnimationState, currentAnimation, frameNumber, tickCount)
, loadAnimations
, getAnimationSet
, getAnimation
, getFrame
, updateAnimationState
, getCurrentFrame)
where
module SDLAnimations
( AnimationSet()
, Animation()
, AnimationState(AnimationState, currentAnimation, frameNumber, tickCount)
, loadAnimations
, getAnimationSet
, getAnimation
, getFrame
, updateAnimationState
, getCurrentFrame
) where

import Control.Monad
import System.Directory
Expand Down

0 comments on commit 6bef3ef

Please sign in to comment.