dev #25
					 9 changed files with 76 additions and 52 deletions
				
			
		
							
								
								
									
										13
									
								
								README.md
									
										
									
									
									
								
							
							
						
						
									
										13
									
								
								README.md
									
										
									
									
									
								
							|  | @ -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. | These are the keybinds *in* the game. All other keybinds in the menus should be straightforward. | ||||||
| 
 | 
 | ||||||
| | Action     | Primary       | Secondary   | | | Action         | Primary       | Secondary   | | ||||||
| | ---------- | ------------- | ----------- | | | -------------- | ------------- | ----------- | | ||||||
| | Move up    | `Arrow Up`    | `w`         | | | Move up        | `Arrow Up`    | `w`         | | ||||||
| | Move left  | `Arrow Left`  | `a`         | | | Move left      | `Arrow Left`  | `a`         | | ||||||
| | Move down  | `Arrow Down`  | `s`         | | | Move down      | `Arrow Down`  | `s`         | | ||||||
| | Move right | `Arrow Right` | `d`         | | | Move right     | `Arrow Right` | `d`         | | ||||||
|  | | Show inventory | `i`           |             | | ||||||
| 
 | 
 | ||||||
| ### Example playthrough | ### Example playthrough | ||||||
| 
 | 
 | ||||||
|  |  | ||||||
|  | @ -23,6 +23,10 @@ bgColor = white | ||||||
| zoom :: Float | zoom :: Float | ||||||
| zoom = 5.0 | zoom = 5.0 | ||||||
| 
 | 
 | ||||||
|  | -- UI scale | ||||||
|  | uizoom :: Float | ||||||
|  | uizoom = 0.5 | ||||||
|  | 
 | ||||||
| -- Resolution of the texture | -- Resolution of the texture | ||||||
| resolution :: Float | resolution :: Float | ||||||
| resolution = 16 | resolution = 16 | ||||||
|  |  | ||||||
|  | @ -99,9 +99,11 @@ data Direction = North | ||||||
|                deriving (Eq, Show) |                deriving (Eq, Show) | ||||||
| 
 | 
 | ||||||
| data Player = Player { | data Player = Player { | ||||||
|     playerHp  :: HP, |     playerHp      :: HP, | ||||||
|     inventory :: [Item], |     inventory     :: [Item], | ||||||
|     position  :: (X, Y) |     position      :: (X, Y), | ||||||
|  |     showHp        :: Bool, | ||||||
|  |     showInventory :: Bool | ||||||
| } deriving (Eq, Show) | } deriving (Eq, Show) | ||||||
| 
 | 
 | ||||||
| ------------------------------ Condition ----------------------------- | ------------------------------ Condition ----------------------------- | ||||||
|  |  | ||||||
|  | @ -32,16 +32,16 @@ composeInputHandlers (ih:ihs) ev a = composeInputHandlers ihs ev (ih ev a) | ||||||
| 
 | 
 | ||||||
| -- Handle any event | -- Handle any event | ||||||
| handle :: Event -> (a -> a) -> InputHandler a | handle :: Event -> (a -> a) -> InputHandler a | ||||||
| handle (EventKey key _ _ _) = handleKey key | handle (EventKey key state _ _) = handleKey key state | ||||||
| -- handle (EventMotion _)      = undefined -- TODO | -- handle (EventMotion _)      = undefined -- TODO | ||||||
| -- handle (EventResize _)      = undefined -- TODO | -- handle (EventResize _)      = undefined -- TODO | ||||||
| handle _                    = const (const id) | handle _                        = const (const id) | ||||||
| 
 | 
 | ||||||
| -- Handle a event by pressing a key | -- Handle a event by pressing a key | ||||||
| handleKey :: Key -> (a -> a) -> InputHandler a | handleKey :: Key -> KeyState -> (a -> a) -> InputHandler a | ||||||
| handleKey (SpecialKey  sk) = handleSpecialKey sk | handleKey (SpecialKey  sk) s = handleSpecialKey sk s | ||||||
| handleKey (Char        c ) = handleCharKey c | handleKey (Char        c ) s = handleCharKey c s | ||||||
| handleKey (MouseButton _ ) = const (const id) | handleKey (MouseButton _ ) _ = const (const id) | ||||||
| 
 | 
 | ||||||
| -- Handle any key, equivalent to "Press any key to start" | -- Handle any key, equivalent to "Press any key to start" | ||||||
| handleAnyKey :: (a -> a) -> InputHandler a | handleAnyKey :: (a -> a) -> InputHandler a | ||||||
|  | @ -50,14 +50,14 @@ handleAnyKey _ _                     = id | ||||||
| 
 | 
 | ||||||
| --------------------------- Help functions --------------------------- | --------------------------- Help functions --------------------------- | ||||||
| 
 | 
 | ||||||
| handleCharKey :: Char -> (a -> a) -> InputHandler a | handleCharKey :: Char -> KeyState -> (a -> a) -> InputHandler a | ||||||
| handleCharKey c1 f (EventKey (Char c2) Down _ _) | handleCharKey c1 s1 f (EventKey (Char c2) s2 _ _) | ||||||
|     | c1 == c2  = f |     | c1 == c2 && s1 == s2 = f | ||||||
|     | otherwise = id |     | otherwise            = id | ||||||
| handleCharKey _  _ _ = id | handleCharKey _  _ _ _ = id | ||||||
| 
 | 
 | ||||||
| handleSpecialKey :: SpecialKey -> (a -> a) -> InputHandler a | handleSpecialKey :: SpecialKey -> KeyState -> (a -> a) -> InputHandler a | ||||||
| handleSpecialKey sk1 f (EventKey (SpecialKey sk2) Down _ _) | handleSpecialKey sk1 s1 f (EventKey (SpecialKey sk2) s2 _ _) | ||||||
|     | sk1 == sk2 = f |     | sk1 == sk2 && s1 == s2 = f | ||||||
|     | otherwise  = id |     | otherwise  = id | ||||||
| handleSpecialKey _   _ _ = id | handleSpecialKey _   _ _ _ = id | ||||||
|  | @ -6,7 +6,7 @@ import RPGEngine.Input.Core (InputHandler, composeInputHandlers, handleKey, List | ||||||
| 
 | 
 | ||||||
| import RPGEngine.Data (Game (..), State (..), Direction (..)) | import RPGEngine.Data (Game (..), State (..), Direction (..)) | ||||||
| import Graphics.Gloss.Interface.IO.Game (Key(..)) | 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.Config (levelFolder) | ||||||
| import RPGEngine.Parse (parse) | import RPGEngine.Parse (parse) | ||||||
| 
 | 
 | ||||||
|  | @ -14,10 +14,10 @@ import RPGEngine.Parse (parse) | ||||||
| 
 | 
 | ||||||
| handleInputLevelSelection :: InputHandler Game | handleInputLevelSelection :: InputHandler Game | ||||||
| handleInputLevelSelection = composeInputHandlers [ | handleInputLevelSelection = composeInputHandlers [ | ||||||
|     handleKey (SpecialKey KeySpace) selectLevel, |     handleKey (SpecialKey KeySpace) Down selectLevel, | ||||||
| 
 | 
 | ||||||
|     handleKey (SpecialKey KeyUp)   $ moveSelector North, |     handleKey (SpecialKey KeyUp)   Down $ moveSelector North, | ||||||
|     handleKey (SpecialKey KeyDown) $ moveSelector South |     handleKey (SpecialKey KeyDown) Down $ moveSelector South | ||||||
|     ] |     ] | ||||||
| 
 | 
 | ||||||
| ---------------------------------------------------------------------- | ---------------------------------------------------------------------- | ||||||
|  |  | ||||||
|  | @ -4,32 +4,36 @@ module RPGEngine.Input.Playing | ||||||
| , spawnPlayer | , spawnPlayer | ||||||
| ) where | ) 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 (..), Layout(..), Level(..), Physical(..), Player(..), State(..), X, Y, Direction (..)) | ||||||
| import RPGEngine.Data.Game (isLegalMove, isPlayerDead, isPlayerAtExit) | import RPGEngine.Data.Game (isLegalMove, isPlayerDead, isPlayerAtExit) | ||||||
| import RPGEngine.Data.Level (directionOffsets, findFirstOf) | import RPGEngine.Data.Level (directionOffsets, findFirstOf) | ||||||
|  | 
 | ||||||
| import Data.Maybe (fromJust, isNothing) | import Data.Maybe (fromJust, isNothing) | ||||||
| import Graphics.Gloss.Interface.IO.Game (Key(..)) | 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 ------------------------------ | ------------------------------ Exported ------------------------------ | ||||||
| 
 | 
 | ||||||
| handleInputPlaying :: InputHandler Game | handleInputPlaying :: InputHandler Game | ||||||
| handleInputPlaying = composeInputHandlers [ | handleInputPlaying = composeInputHandlers [ | ||||||
|     -- Pause the game |     -- Pause the game | ||||||
|     handleKey (Char 'p') pauseGame, |     handleKey (Char 'p') Down pauseGame, | ||||||
| 
 | 
 | ||||||
|     -- Player movement |     -- Player movement | ||||||
|     handleKey (SpecialKey KeyUp)    $ movePlayer North, |     handleKey (SpecialKey KeyUp)    Down $ movePlayer North, | ||||||
|     handleKey (SpecialKey KeyRight) $ movePlayer East, |     handleKey (SpecialKey KeyRight) Down $ movePlayer East, | ||||||
|     handleKey (SpecialKey KeyDown)  $ movePlayer South, |     handleKey (SpecialKey KeyDown)  Down $ movePlayer South, | ||||||
|     handleKey (SpecialKey KeyLeft)  $ movePlayer West, |     handleKey (SpecialKey KeyLeft)  Down $ movePlayer West, | ||||||
| 
 | 
 | ||||||
|     handleKey (Char 'w') $ movePlayer North, |     handleKey (Char 'w') Down $ movePlayer North, | ||||||
|     handleKey (Char 'd') $ movePlayer East, |     handleKey (Char 'd') Down $ movePlayer East, | ||||||
|     handleKey (Char 's') $ movePlayer South, |     handleKey (Char 's') Down $ movePlayer South, | ||||||
|     handleKey (Char 'a') $ movePlayer West |     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 |           (xD, yD)  = directionOffsets dir | ||||||
| movePlayer _ g = g | 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 | -- Map all Physicals onto coordinates | ||||||
| putCoords :: Level -> [(X, Y, Physical)] | putCoords :: Level -> [(X, Y, Physical)] | ||||||
| putCoords l@Level{ layout = lay } = concatMap (\(a, bs) -> map (\(b, c) -> (b, a, c)) bs) numberedList | putCoords l@Level{ layout = lay } = concatMap (\(a, bs) -> map (\(b, c) -> (b, a, c)) bs) numberedList | ||||||
|  |  | ||||||
|  | @ -33,4 +33,3 @@ render Game{ state = s@Playing{}        } = renderPlaying s | ||||||
| render Game{ state = s@Paused{}         } = renderPaused s | render Game{ state = s@Paused{}         } = renderPaused s | ||||||
| render Game{ state = s@Win              } = renderWin s | render Game{ state = s@Win              } = renderWin s | ||||||
| render Game{ state = s@Lose{}           } = renderLose s | render Game{ state = s@Lose{}           } = renderLose s | ||||||
| render _ = blank |  | ||||||
|  | @ -4,7 +4,7 @@ module RPGEngine.Render.LevelSelection | ||||||
| 
 | 
 | ||||||
| import RPGEngine.Render.Core (Renderer) | import RPGEngine.Render.Core (Renderer) | ||||||
| 
 | 
 | ||||||
| import RPGEngine.Config (resolution, zoom) | import RPGEngine.Config (resolution, zoom, uizoom) | ||||||
| import RPGEngine.Data (State (..)) | import RPGEngine.Data (State (..)) | ||||||
| 
 | 
 | ||||||
| import Graphics.Gloss ( pictures, color, text, translate, blank ) | 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 |     where everything       = pictures $ map render entries | ||||||
|           sel              = selection selector |           sel              = selection selector | ||||||
|           entries          = zip [0::Int .. ] list |           entries          = zip [0::Int .. ] list | ||||||
|           render (i, path) | i == sel  = color red $ scale zoomed zoomed $ translate 0 (offset i) $ text path |           render (i, path) | i == sel  = color red $ scale uizoom uizoom $ translate 0 (offset i) $ text path | ||||||
|                            | otherwise = scale zoomed zoomed $ translate 0 (offset i) $ text path |                            | otherwise = scale uizoom uizoom $ translate 0 (offset i) $ text path | ||||||
|           zoomed           = 0.1 * zoom |           offset i         = negate (250 * uizoom * fromIntegral i) | ||||||
|           offset i         = negate (2 * resolution * zoom * fromIntegral i) |  | ||||||
| renderLevelList _ = blank | renderLevelList _ = blank | ||||||
|  | @ -2,20 +2,21 @@ module RPGEngine.Render.Playing | ||||||
| ( renderPlaying | ( renderPlaying | ||||||
| ) where | ) 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 RPGEngine.Data (State(..), Player (..), Game (..), Level (..), Layout, Physical (..), Item (..), Entity (..)) | ||||||
| 
 | 
 | ||||||
| import Graphics.Gloss ( pictures, Picture, translate ) | import Graphics.Gloss ( pictures, Picture, translate, white ) | ||||||
| import Graphics.Gloss.Data.Picture (blank) | import Graphics.Gloss.Data.Picture ( blank, text, color, scale ) | ||||||
| 
 | 
 | ||||||
| ------------------------------ Exported ------------------------------ | ------------------------------ Exported ------------------------------ | ||||||
| 
 | 
 | ||||||
| renderPlaying :: Renderer State | renderPlaying :: Renderer State | ||||||
| renderPlaying Playing { level = lvl, player = player } = pictures [ | renderPlaying Playing { level = lvl, player = player } = pictures [ | ||||||
|     renderLevel lvl, |     renderLevel lvl, | ||||||
|     renderPlayer player |     renderPlayer player, | ||||||
|  |     renderInventory player | ||||||
|     ] |     ] | ||||||
| renderPlaying _ = blank | renderPlaying _ = blank | ||||||
| 
 | 
 | ||||||
|  | @ -84,3 +85,11 @@ renderEntities list = pictures $ map renderEntity list | ||||||
| renderEntity :: Entity -> Picture | renderEntity :: Entity -> Picture | ||||||
| renderEntity Entity{ entityId = id, entityX = x, entityY = y} = setRenderPos x y image | 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) | ||||||
		Reference in a new issue