#5 Render inventory when pressing i

This commit is contained in:
Tibo De Peuter 2022-12-22 14:35:58 +01:00
parent f529fc5237
commit d0302c3156
9 changed files with 76 additions and 52 deletions

View file

@ -51,12 +51,13 @@ This README serves as both documentation and project report, so excuse the detai
These are the keybinds *in* the game. All other keybinds in the menus should be straightforward.
| Action | Primary | Secondary |
| ---------- | ------------- | ----------- |
| Move up | `Arrow Up` | `w` |
| Move left | `Arrow Left` | `a` |
| Move down | `Arrow Down` | `s` |
| Move right | `Arrow Right` | `d` |
| Action | Primary | Secondary |
| -------------- | ------------- | ----------- |
| Move up | `Arrow Up` | `w` |
| Move left | `Arrow Left` | `a` |
| Move down | `Arrow Down` | `s` |
| Move right | `Arrow Right` | `d` |
| Show inventory | `i` | |
### Example playthrough

View file

@ -23,6 +23,10 @@ bgColor = white
zoom :: Float
zoom = 5.0
-- UI scale
uizoom :: Float
uizoom = 0.5
-- Resolution of the texture
resolution :: Float
resolution = 16

View file

@ -99,9 +99,11 @@ data Direction = North
deriving (Eq, Show)
data Player = Player {
playerHp :: HP,
inventory :: [Item],
position :: (X, Y)
playerHp :: HP,
inventory :: [Item],
position :: (X, Y),
showHp :: Bool,
showInventory :: Bool
} deriving (Eq, Show)
------------------------------ Condition -----------------------------

View file

@ -32,16 +32,16 @@ composeInputHandlers (ih:ihs) ev a = composeInputHandlers ihs ev (ih ev a)
-- Handle any event
handle :: Event -> (a -> a) -> InputHandler a
handle (EventKey key _ _ _) = handleKey key
handle (EventKey key state _ _) = handleKey key state
-- handle (EventMotion _) = undefined -- TODO
-- handle (EventResize _) = undefined -- TODO
handle _ = const (const id)
handle _ = const (const id)
-- Handle a event by pressing a key
handleKey :: Key -> (a -> a) -> InputHandler a
handleKey (SpecialKey sk) = handleSpecialKey sk
handleKey (Char c ) = handleCharKey c
handleKey (MouseButton _ ) = const (const id)
handleKey :: Key -> KeyState -> (a -> a) -> InputHandler a
handleKey (SpecialKey sk) s = handleSpecialKey sk s
handleKey (Char c ) s = handleCharKey c s
handleKey (MouseButton _ ) _ = const (const id)
-- Handle any key, equivalent to "Press any key to start"
handleAnyKey :: (a -> a) -> InputHandler a
@ -50,14 +50,14 @@ handleAnyKey _ _ = id
--------------------------- Help functions ---------------------------
handleCharKey :: Char -> (a -> a) -> InputHandler a
handleCharKey c1 f (EventKey (Char c2) Down _ _)
| c1 == c2 = f
| otherwise = id
handleCharKey _ _ _ = id
handleCharKey :: Char -> KeyState -> (a -> a) -> InputHandler a
handleCharKey c1 s1 f (EventKey (Char c2) s2 _ _)
| c1 == c2 && s1 == s2 = f
| otherwise = id
handleCharKey _ _ _ _ = id
handleSpecialKey :: SpecialKey -> (a -> a) -> InputHandler a
handleSpecialKey sk1 f (EventKey (SpecialKey sk2) Down _ _)
| sk1 == sk2 = f
handleSpecialKey :: SpecialKey -> KeyState -> (a -> a) -> InputHandler a
handleSpecialKey sk1 s1 f (EventKey (SpecialKey sk2) s2 _ _)
| sk1 == sk2 && s1 == s2 = f
| otherwise = id
handleSpecialKey _ _ _ = id
handleSpecialKey _ _ _ _ = id

View file

@ -6,7 +6,7 @@ import RPGEngine.Input.Core (InputHandler, composeInputHandlers, handleKey, List
import RPGEngine.Data (Game (..), State (..), Direction (..))
import Graphics.Gloss.Interface.IO.Game (Key(..))
import Graphics.Gloss.Interface.IO.Interact (SpecialKey(..))
import Graphics.Gloss.Interface.IO.Interact (SpecialKey(..), KeyState(..))
import RPGEngine.Config (levelFolder)
import RPGEngine.Parse (parse)
@ -14,10 +14,10 @@ import RPGEngine.Parse (parse)
handleInputLevelSelection :: InputHandler Game
handleInputLevelSelection = composeInputHandlers [
handleKey (SpecialKey KeySpace) selectLevel,
handleKey (SpecialKey KeySpace) Down selectLevel,
handleKey (SpecialKey KeyUp) $ moveSelector North,
handleKey (SpecialKey KeyDown) $ moveSelector South
handleKey (SpecialKey KeyUp) Down $ moveSelector North,
handleKey (SpecialKey KeyDown) Down $ moveSelector South
]
----------------------------------------------------------------------

View file

@ -4,32 +4,36 @@ module RPGEngine.Input.Playing
, spawnPlayer
) where
import RPGEngine.Input.Core (InputHandler, handleKey, composeInputHandlers)
import RPGEngine.Input.Core (InputHandler, handle, handleKey, composeInputHandlers)
import RPGEngine.Data (Game (..), Layout(..), Level(..), Physical(..), Player(..), State(..), X, Y, Direction (..))
import RPGEngine.Data.Game (isLegalMove, isPlayerDead, isPlayerAtExit)
import RPGEngine.Data.Level (directionOffsets, findFirstOf)
import Data.Maybe (fromJust, isNothing)
import Graphics.Gloss.Interface.IO.Game (Key(..))
import Graphics.Gloss.Interface.IO.Interact (SpecialKey(..))
import Graphics.Gloss.Interface.IO.Interact (SpecialKey(..), KeyState(..), Event(..), KeyState(..))
------------------------------ Exported ------------------------------
handleInputPlaying :: InputHandler Game
handleInputPlaying = composeInputHandlers [
-- Pause the game
handleKey (Char 'p') pauseGame,
handleKey (Char 'p') Down pauseGame,
-- Player movement
handleKey (SpecialKey KeyUp) $ movePlayer North,
handleKey (SpecialKey KeyRight) $ movePlayer East,
handleKey (SpecialKey KeyDown) $ movePlayer South,
handleKey (SpecialKey KeyLeft) $ movePlayer West,
handleKey (SpecialKey KeyUp) Down $ movePlayer North,
handleKey (SpecialKey KeyRight) Down $ movePlayer East,
handleKey (SpecialKey KeyDown) Down $ movePlayer South,
handleKey (SpecialKey KeyLeft) Down $ movePlayer West,
handleKey (Char 'w') $ movePlayer North,
handleKey (Char 'd') $ movePlayer East,
handleKey (Char 's') $ movePlayer South,
handleKey (Char 'a') $ movePlayer West
handleKey (Char 'w') Down $ movePlayer North,
handleKey (Char 'd') Down $ movePlayer East,
handleKey (Char 's') Down $ movePlayer South,
handleKey (Char 'a') Down $ movePlayer West,
handleKey (Char 'i') Down $ toggleInventoryShown True,
handleKey (Char 'i') Up $ toggleInventoryShown False
]
----------------------------------------------------------------------
@ -76,6 +80,12 @@ movePlayer dir g@Game{ state = s@Playing{ player = p@Player{ position = (x, y) }
(xD, yD) = directionOffsets dir
movePlayer _ g = g
toggleInventoryShown :: Bool -> Game -> Game
toggleInventoryShown shown g@Game{ state = s@Playing{ player = p }}= newGame
where newGame = g{ state = newState }
newState = s{ player = newPlayer }
newPlayer = p{ showInventory = shown }
-- 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

View file

@ -32,5 +32,4 @@ render Game{ state = s@LevelSelection{} } = renderLevelSelection s
render Game{ state = s@Playing{} } = renderPlaying s
render Game{ state = s@Paused{} } = renderPaused s
render Game{ state = s@Win } = renderWin s
render Game{ state = s@Lose{} } = renderLose s
render _ = blank
render Game{ state = s@Lose{} } = renderLose s

View file

@ -4,7 +4,7 @@ module RPGEngine.Render.LevelSelection
import RPGEngine.Render.Core (Renderer)
import RPGEngine.Config (resolution, zoom)
import RPGEngine.Config (resolution, zoom, uizoom)
import RPGEngine.Data (State (..))
import Graphics.Gloss ( pictures, color, text, translate, blank )
@ -25,8 +25,7 @@ renderLevelList LevelSelection{ levelList = list, selector = selector } = everyt
where everything = pictures $ map render entries
sel = selection selector
entries = zip [0::Int .. ] list
render (i, path) | i == sel = color red $ scale zoomed zoomed $ translate 0 (offset i) $ text path
| otherwise = scale zoomed zoomed $ translate 0 (offset i) $ text path
zoomed = 0.1 * zoom
offset i = negate (2 * resolution * zoom * fromIntegral i)
render (i, path) | i == sel = color red $ scale uizoom uizoom $ translate 0 (offset i) $ text path
| otherwise = scale uizoom uizoom $ translate 0 (offset i) $ text path
offset i = negate (250 * uizoom * fromIntegral i)
renderLevelList _ = blank

View file

@ -2,20 +2,21 @@ module RPGEngine.Render.Playing
( renderPlaying
) where
import RPGEngine.Render.Core (Renderer, getRender, setRenderPos)
import RPGEngine.Render.Core (Renderer, getRender, setRenderPos, overlay)
import RPGEngine.Config (resolution, zoom)
import RPGEngine.Config (resolution, zoom, uizoom)
import RPGEngine.Data (State(..), Player (..), Game (..), Level (..), Layout, Physical (..), Item (..), Entity (..))
import Graphics.Gloss ( pictures, Picture, translate )
import Graphics.Gloss.Data.Picture (blank)
import Graphics.Gloss ( pictures, Picture, translate, white )
import Graphics.Gloss.Data.Picture ( blank, text, color, scale )
------------------------------ Exported ------------------------------
renderPlaying :: Renderer State
renderPlaying Playing { level = lvl, player = player } = pictures [
renderLevel lvl,
renderPlayer player
renderPlayer player,
renderInventory player
]
renderPlaying _ = blank
@ -83,4 +84,12 @@ renderEntities list = pictures $ map renderEntity list
renderEntity :: Entity -> Picture
renderEntity Entity{ entityId = id, entityX = x, entityY = y} = setRenderPos x y image
where image = getRender id
where image = getRender id
renderInventory :: Player -> Picture
renderInventory Player{ showInventory = False } = blank
renderInventory Player{ inventory = list } = pictures [overlay, title, items]
where title = translate 0 (offset (-1)) $ scale uizoom uizoom $ color white $ text "Inventory"
items = pictures $ map move $ zip [0::Int ..] (map (getRender . itemId) list)
move (i, pic) = translate 0 (offset i) pic
offset i = negate (zoom * resolution * fromIntegral i)