#3 Restrict player going places
This commit is contained in:
parent
5c8cee8104
commit
0786a41006
6 changed files with 78 additions and 21 deletions
|
@ -14,9 +14,10 @@ data Game = Game {
|
||||||
------------------------------- Level --------------------------------
|
------------------------------- Level --------------------------------
|
||||||
|
|
||||||
data Level = Level {
|
data Level = Level {
|
||||||
layout :: Layout,
|
layout :: Layout,
|
||||||
items :: [Item],
|
coordlayout :: [(X, Y, Physical)],
|
||||||
entities :: [Entity]
|
items :: [Item],
|
||||||
|
entities :: [Entity]
|
||||||
} deriving (Eq, Show)
|
} deriving (Eq, Show)
|
||||||
|
|
||||||
type Layout = [Strip]
|
type Layout = [Strip]
|
||||||
|
@ -37,7 +38,7 @@ type Y = Int
|
||||||
data Player = Player {
|
data Player = Player {
|
||||||
playerHp :: Maybe Int,
|
playerHp :: Maybe Int,
|
||||||
inventory :: [Item],
|
inventory :: [Item],
|
||||||
coord :: (X, Y)
|
position :: (X, Y)
|
||||||
} deriving (Eq, Show)
|
} deriving (Eq, Show)
|
||||||
|
|
||||||
instance Living Player where
|
instance Living Player where
|
||||||
|
|
|
@ -1,6 +1,8 @@
|
||||||
module RPGEngine.Data.Defaults where
|
module RPGEngine.Data.Defaults where
|
||||||
|
|
||||||
import RPGEngine.Data
|
import RPGEngine.Data
|
||||||
|
import RPGEngine.Input.Player (spawnPlayer)
|
||||||
|
import RPGEngine.Input.Level (putCoords)
|
||||||
|
|
||||||
defaultEntity :: Entity
|
defaultEntity :: Entity
|
||||||
defaultEntity = Entity {
|
defaultEntity = Entity {
|
||||||
|
@ -21,7 +23,7 @@ initGame = Game {
|
||||||
state = defaultState,
|
state = defaultState,
|
||||||
playing = defaultLevel,
|
playing = defaultLevel,
|
||||||
levels = [defaultLevel],
|
levels = [defaultLevel],
|
||||||
player = defaultPlayer
|
player = spawnPlayer defaultLevel defaultPlayer
|
||||||
}
|
}
|
||||||
|
|
||||||
defaultItem :: Item
|
defaultItem :: Item
|
||||||
|
@ -46,6 +48,7 @@ defaultLayout = [
|
||||||
defaultLevel :: Level
|
defaultLevel :: Level
|
||||||
defaultLevel = Level {
|
defaultLevel = Level {
|
||||||
layout = defaultLayout,
|
layout = defaultLayout,
|
||||||
|
coordlayout = putCoords defaultLevel, -- TODO This should go
|
||||||
items = [],
|
items = [],
|
||||||
entities = []
|
entities = []
|
||||||
}
|
}
|
||||||
|
@ -54,7 +57,7 @@ defaultPlayer :: Player
|
||||||
defaultPlayer = Player {
|
defaultPlayer = Player {
|
||||||
playerHp = Prelude.Nothing, -- Compares to infinity
|
playerHp = Prelude.Nothing, -- Compares to infinity
|
||||||
inventory = [],
|
inventory = [],
|
||||||
coord = (0, 0)
|
position = (0, 0)
|
||||||
}
|
}
|
||||||
|
|
||||||
-- Default state of the game, Menu
|
-- Default state of the game, Menu
|
||||||
|
|
27
lib/RPGEngine/Input/Level.hs
Normal file
27
lib/RPGEngine/Input/Level.hs
Normal file
|
@ -0,0 +1,27 @@
|
||||||
|
module RPGEngine.Input.Level
|
||||||
|
( putCoords
|
||||||
|
, findFirst
|
||||||
|
, whatIsAt
|
||||||
|
) where
|
||||||
|
import RPGEngine.Data (Level (..), Y, X, Physical(..))
|
||||||
|
|
||||||
|
-- Map all Physicals onto coordinates
|
||||||
|
putCoords :: Level -> [(X, Y, Physical)]
|
||||||
|
putCoords l@Level{ layout = lay } = concatMap (\(a, bs) -> map (\(b, c) -> (b, a, c)) bs) numberedList
|
||||||
|
where numberedStrips = zip [0::Int .. ] lay
|
||||||
|
numberedList = map (\(x, strip) -> (x, zip [0::Int ..] strip)) numberedStrips
|
||||||
|
|
||||||
|
-- Find first position of a Physical
|
||||||
|
-- Graceful exit by giving Nothing if there is nothing found.
|
||||||
|
findFirst :: Level -> Physical -> Maybe (X, Y)
|
||||||
|
findFirst l@Level{ coordlayout = lay } physical = try
|
||||||
|
where matches = filter (\(x, y, v) -> v == physical) lay
|
||||||
|
try | not (null matches) = Just $ (\(x, y, _) -> (x, y)) $ head matches
|
||||||
|
| otherwise = Nothing
|
||||||
|
|
||||||
|
-- What is located at a given position in the level?
|
||||||
|
whatIsAt :: (X, Y) -> Level -> Physical
|
||||||
|
whatIsAt pos lvl@Level{ coordlayout = lay } = try
|
||||||
|
where matches = map (\(_, _, v) -> v) $ filter (\(x, y, v) -> (x, y) == pos) lay
|
||||||
|
try | not (null matches) = head matches
|
||||||
|
| otherwise = Void
|
|
@ -1,19 +1,44 @@
|
||||||
module RPGEngine.Input.Player
|
module RPGEngine.Input.Player
|
||||||
( movePlayer
|
( spawnPlayer
|
||||||
|
, movePlayer
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import RPGEngine.Data (Game(..), Direction(..), Player(..), X, Y)
|
import RPGEngine.Data (Game(..), Direction(..), Player(..), X, Y, Physical (..), Level(..))
|
||||||
|
import RPGEngine.Input.Level (whatIsAt, findFirst)
|
||||||
|
import Data.Maybe (fromJust, isNothing)
|
||||||
|
|
||||||
|
----------------------------- Constants ------------------------------
|
||||||
|
|
||||||
movePlayer :: Direction -> Game -> Game
|
|
||||||
movePlayer dir g@Game{ player = p@Player{ coord = (x, y) }} = newGame
|
|
||||||
where newGame = g{ player = newPlayer }
|
|
||||||
newPlayer = p{ coord = newCoord }
|
|
||||||
newCoord = (x + xD, y + yD)
|
|
||||||
(xD, yD) = diffs dir
|
|
||||||
|
|
||||||
diffs :: Direction -> (X, Y)
|
diffs :: Direction -> (X, Y)
|
||||||
diffs North = (0, 1)
|
diffs North = ( 0, 1)
|
||||||
diffs East = (1, 0)
|
diffs East = ( 1, 0)
|
||||||
diffs South = (0, -1)
|
diffs South = ( 0, -1)
|
||||||
diffs West = (-1, 0)
|
diffs West = (-1, 0)
|
||||||
diffs Center = (0, 0)
|
diffs Center = ( 0, 0)
|
||||||
|
|
||||||
|
----------------------------------------------------------------------
|
||||||
|
|
||||||
|
-- Set the initial position of the player in a given level.
|
||||||
|
spawnPlayer :: Level -> Player -> Player
|
||||||
|
spawnPlayer l@Level{ layout = lay } p@Player{ position = prevPos } = p{ position = newPos }
|
||||||
|
where try = findFirst l Entrance
|
||||||
|
newPos | isNothing try = prevPos
|
||||||
|
| otherwise = fromJust try
|
||||||
|
|
||||||
|
-- Move a player in a direction if possible.
|
||||||
|
movePlayer :: Direction -> Game -> Game
|
||||||
|
movePlayer dir g@Game{ player = p@Player{ position = (x, y) }} = newGame
|
||||||
|
where newGame = g{ player = newPlayer }
|
||||||
|
newPlayer = p{ position = newCoord }
|
||||||
|
newCoord | isLegalMove dir g = (x + xD, y + yD)
|
||||||
|
| otherwise = (x, y)
|
||||||
|
(xD, yD) = diffs dir
|
||||||
|
|
||||||
|
-- Check if a move is legal by checking what is located at the new position.
|
||||||
|
isLegalMove :: Direction -> Game -> Bool
|
||||||
|
isLegalMove dir g@Game{ playing = lvl, player = p@Player{ position = (x, y) }} = legality
|
||||||
|
where legality = physical `elem` [Walkable, Entrance, Exit]
|
||||||
|
physical = whatIsAt newPos lvl
|
||||||
|
newPos = (x + xD, y + yD)
|
||||||
|
(xD, yD) = diffs dir
|
|
@ -8,4 +8,4 @@ import Graphics.Gloss (Picture, text)
|
||||||
import RPGEngine.Render.Core (getRender, setRenderPos)
|
import RPGEngine.Render.Core (getRender, setRenderPos)
|
||||||
|
|
||||||
renderPlayer :: Player -> Picture
|
renderPlayer :: Player -> Picture
|
||||||
renderPlayer Player{ coord = (x, y) } = setRenderPos x y $ getRender "player"
|
renderPlayer Player{ position = (x, y) } = setRenderPos x y $ getRender "player"
|
|
@ -19,6 +19,7 @@ library
|
||||||
|
|
||||||
RPGEngine.Input
|
RPGEngine.Input
|
||||||
RPGEngine.Input.Core
|
RPGEngine.Input.Core
|
||||||
|
RPGEngine.Input.Level
|
||||||
RPGEngine.Input.Player
|
RPGEngine.Input.Player
|
||||||
|
|
||||||
RPGEngine.Parse
|
RPGEngine.Parse
|
||||||
|
|
Reference in a new issue