dev #25
					 13 changed files with 223 additions and 33 deletions
				
			
		|  | @ -57,7 +57,8 @@ These are the keybinds *in* the game. All other keybinds in the menus should be | ||||||
| | 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`           |             | | | Interaction    | `Space`       | `f`         | | ||||||
|  | | Show inventory | `i`           | `Tab`       | | ||||||
| | Restart level  | `r`           |             | | | Restart level  | `r`           |             | | ||||||
| | Quit game      | `Esc`         |             | | | Quit game      | `Esc`         |             | | ||||||
| 
 | 
 | ||||||
|  |  | ||||||
|  | @ -27,14 +27,22 @@ data State = Menu | ||||||
|                                level     :: Level, |                                level     :: Level, | ||||||
|                                player    :: Player, |                                player    :: Player, | ||||||
|                                restart   :: State         } |                                restart   :: State         } | ||||||
|  |            -- Selecting an action | ||||||
|  |            | ActionSelection { actionList :: [Action], | ||||||
|  |                                selector  :: ListSelector, | ||||||
|  |                                -- The player of this state will be used to interact | ||||||
|  |                                continue  :: State         } | ||||||
|            -- Paused while playing a level |            -- Paused while playing a level | ||||||
|            | Paused          { continue  :: State         } |            | Paused          { continue  :: State         } | ||||||
|            -- Won a level |            -- Won a level | ||||||
|            | Win |            | Win | ||||||
|            -- Lost a level |            -- Lost a level | ||||||
|            | Lose            { restart   :: State         } |            | Lose            { restart   :: State         } | ||||||
|  |            | Error Message | ||||||
|            deriving (Eq, Show) |            deriving (Eq, Show) | ||||||
| 
 | 
 | ||||||
|  | type Message = String | ||||||
|  | 
 | ||||||
| ------------------------------- Level -------------------------------- | ------------------------------- Level -------------------------------- | ||||||
| 
 | 
 | ||||||
| data Level = Level { | data Level = Level { | ||||||
|  |  | ||||||
|  | @ -5,8 +5,9 @@ where | ||||||
| import GHC.IO (unsafePerformIO) | import GHC.IO (unsafePerformIO) | ||||||
| import System.Directory (getDirectoryContents) | import System.Directory (getDirectoryContents) | ||||||
| import RPGEngine.Input.Core (ListSelector(..)) | import RPGEngine.Input.Core (ListSelector(..)) | ||||||
| import RPGEngine.Data (Level (..), Physical (..), Direction (..), Entity (..), Game (..), Item (..), Player (..), State (..), X, Y, Layout) | import RPGEngine.Data (Action(..), Level (..), Physical (..), Direction (..), Entity (..), Game (..), Item (..), Player (..), State (..), X, Y, Layout, Condition (InventoryFull, InventoryContains, Not, AlwaysFalse)) | ||||||
| import RPGEngine.Config (levelFolder) | import RPGEngine.Config (levelFolder) | ||||||
|  | import Data.Foldable (find) | ||||||
| 
 | 
 | ||||||
| ------------------------------ Exported ------------------------------ | ------------------------------ Exported ------------------------------ | ||||||
| 
 | 
 | ||||||
|  | @ -25,6 +26,17 @@ findAt pos lvl@Level{ index = index } = try | ||||||
|           try     | not (null matches) = head matches |           try     | not (null matches) = head matches | ||||||
|                   | otherwise          = Void |                   | otherwise          = Void | ||||||
| 
 | 
 | ||||||
|  | hasAt :: (X, Y) -> Level -> Maybe (Either Item Entity) | ||||||
|  | hasAt pos level = match firstItem firstEntity | ||||||
|  |     where match :: Maybe Item -> Maybe Entity -> Maybe (Either Item Entity) | ||||||
|  |           match (Just a) _ = Just $ Left a | ||||||
|  |           match _ (Just a) = Just $ Right a | ||||||
|  |           match _ _        = Nothing | ||||||
|  |           firstEntity = find ((== pos) . getECoord) $ entities level | ||||||
|  |           getECoord e = (entityX e, entityY e) | ||||||
|  |           firstItem   = find ((== pos) . getICoord) $ items level | ||||||
|  |           getICoord i = (itemX i, itemY i) | ||||||
|  | 
 | ||||||
| directionOffsets :: Direction -> (X, Y) | directionOffsets :: Direction -> (X, Y) | ||||||
| directionOffsets North  = ( 0,  1) | directionOffsets North  = ( 0,  1) | ||||||
| directionOffsets East   = ( 1,  0) | directionOffsets East   = ( 1,  0) | ||||||
|  | @ -34,3 +46,28 @@ directionOffsets Stay   = ( 0,  0) | ||||||
| 
 | 
 | ||||||
| getLevelList :: [FilePath] | getLevelList :: [FilePath] | ||||||
| getLevelList = drop 2 $ unsafePerformIO $ getDirectoryContents levelFolder | getLevelList = drop 2 $ unsafePerformIO $ getDirectoryContents levelFolder | ||||||
|  | 
 | ||||||
|  | -- Get the actions of either an entity or an item | ||||||
|  | getActions :: Either Item Entity -> [([Condition], Action)] | ||||||
|  | getActions (Left item)    = itemActions item | ||||||
|  | getActions (Right entity) = entityActions entity | ||||||
|  | 
 | ||||||
|  | getActionText :: Action -> String | ||||||
|  | getActionText Leave            = "Leave" | ||||||
|  | getActionText (RetrieveItem _) = "Pick up" | ||||||
|  | getActionText (UseItem _)      = "Use item" | ||||||
|  | getActionText _ = "ERROR" | ||||||
|  | 
 | ||||||
|  | -- TODO Check conditions | ||||||
|  | -- Filter based on the conditions, keep only the actions of which the | ||||||
|  | -- conditions are met. | ||||||
|  | filterActions :: [([Condition], Action)] -> [Action] | ||||||
|  | filterActions [] = [] | ||||||
|  | filterActions ((conditions, action):others) = action:filterActions others | ||||||
|  | 
 | ||||||
|  | -- Check if a condition is met or not. | ||||||
|  | meetsCondition :: Condition -> Bool | ||||||
|  | meetsCondition InventoryFull          = False -- TODO | ||||||
|  | meetsCondition (InventoryContains id) = True -- TODO | ||||||
|  | meetsCondition (Not condition)        = not $ meetsCondition condition | ||||||
|  | meetsCondition AlwaysFalse            = False | ||||||
|  | @ -13,6 +13,7 @@ import RPGEngine.Input.Playing ( handleInputPlaying ) | ||||||
| import RPGEngine.Input.Paused ( handleInputPaused ) | import RPGEngine.Input.Paused ( handleInputPaused ) | ||||||
| import RPGEngine.Input.Win ( handleInputWin ) | import RPGEngine.Input.Win ( handleInputWin ) | ||||||
| import RPGEngine.Input.Lose ( handleInputLose ) | import RPGEngine.Input.Lose ( handleInputLose ) | ||||||
|  | import RPGEngine.Input.ActionSelection (handleInputActionSelection) | ||||||
| 
 | 
 | ||||||
| ------------------------------ Exported ------------------------------ | ------------------------------ Exported ------------------------------ | ||||||
| 
 | 
 | ||||||
|  | @ -24,3 +25,5 @@ handleAllInput ev g@Game{ state = Playing{}        } = handleInputPlaying ev g | ||||||
| handleAllInput ev g@Game{ state = Paused{}         } = handleInputPaused ev g | handleAllInput ev g@Game{ state = Paused{}         } = handleInputPaused ev g | ||||||
| handleAllInput ev g@Game{ state = Win              } = handleInputWin ev g | handleAllInput ev g@Game{ state = Win              } = handleInputWin ev g | ||||||
| handleAllInput ev g@Game{ state = Lose{}           } = handleInputLose ev g | handleAllInput ev g@Game{ state = Lose{}           } = handleInputLose ev g | ||||||
|  | handleAllInput ev g@Game{ state = ActionSelection{}} = handleInputActionSelection ev g | ||||||
|  | handleAllInput ev g@Game{ state = Error _          } = handleAnyKey (\game -> game{ state = Menu}) ev g | ||||||
							
								
								
									
										76
									
								
								lib/RPGEngine/Input/ActionSelection.hs
									
										
									
									
									
										Normal file
									
								
							
							
						
						
									
										76
									
								
								lib/RPGEngine/Input/ActionSelection.hs
									
										
									
									
									
										Normal file
									
								
							|  | @ -0,0 +1,76 @@ | ||||||
|  | module RPGEngine.Input.ActionSelection | ||||||
|  | ( handleInputActionSelection | ||||||
|  | ) where | ||||||
|  | 
 | ||||||
|  | import RPGEngine.Input.Core (InputHandler, handleKey, composeInputHandlers, ListSelector (selection)) | ||||||
|  | 
 | ||||||
|  | import RPGEngine.Data (Game (..), State (..), Direction (..), Action (..), ItemId, EntityId) | ||||||
|  | import Graphics.Gloss.Interface.IO.Game (Key(SpecialKey), SpecialKey (KeyUp, KeyDown)) | ||||||
|  | import Graphics.Gloss.Interface.IO.Interact | ||||||
|  |     ( SpecialKey(..), KeyState(..) ) | ||||||
|  | 
 | ||||||
|  | ------------------------------ Exported ------------------------------ | ||||||
|  | 
 | ||||||
|  | handleInputActionSelection :: InputHandler Game | ||||||
|  | handleInputActionSelection = composeInputHandlers [ | ||||||
|  |     handleKey (SpecialKey KeySpace) Down selectAction, | ||||||
|  | 
 | ||||||
|  |     handleKey (SpecialKey KeyUp)    Down $ moveSelector North, | ||||||
|  |     handleKey (SpecialKey KeyDown)  Down $ moveSelector South | ||||||
|  |     ] | ||||||
|  | 
 | ||||||
|  | ---------------------------------------------------------------------- | ||||||
|  | 
 | ||||||
|  | selectAction :: Game -> Game | ||||||
|  | selectAction game@Game{ state = ActionSelection list selection continue } = newGame | ||||||
|  |     where newGame = game{ state = execute selectedAction continue } | ||||||
|  |           selectedAction = Leave | ||||||
|  | selectAction g = g | ||||||
|  | 
 | ||||||
|  | -- TODO Lift this code from LevelSelection | ||||||
|  | -- Move the selector either up or down | ||||||
|  | moveSelector :: Direction -> Game -> Game | ||||||
|  | moveSelector dir game@Game{ state = state@(ActionSelection list selector _) } = newGame | ||||||
|  |     where newGame      = game{ state = newState } | ||||||
|  |           newState     = state{ selector = newSelector } | ||||||
|  |           newSelector  | constraint = selector{ selection = newSelection } | ||||||
|  |                        | otherwise = selector | ||||||
|  |           constraint   = 0 <= newSelection && newSelection < length list | ||||||
|  |           newSelection = selection selector + diff | ||||||
|  |           diff         | dir == North = -1 | ||||||
|  |                        | dir == South =  1 | ||||||
|  |                        | otherwise    =  0 | ||||||
|  | moveSelector _ g = g{ state = Error "Something went wrong while moving the selector up or down"} | ||||||
|  | 
 | ||||||
|  | ------------------------------ Actions ------------------------------- | ||||||
|  | 
 | ||||||
|  | execute :: Action -> State -> State | ||||||
|  | execute (RetrieveItem id     ) s = pickUpItem id s | ||||||
|  | execute (UseItem      id     ) s = useItem id s | ||||||
|  | execute (DecreaseHp   eid iid) s = decreaseHp eid iid s | ||||||
|  | execute (IncreasePlayerHp iid) s = increasePlayerHp iid s | ||||||
|  | execute _ s = s | ||||||
|  | 
 | ||||||
|  | -- Pick up the item with itemId and put it in the players inventory | ||||||
|  | pickUpItem :: ItemId -> State -> State | ||||||
|  | pickUpItem _ s = s -- TODO | ||||||
|  | 
 | ||||||
|  | -- Use an item on the player | ||||||
|  | useItem :: ItemId -> State -> State -- TODO | ||||||
|  | useItem _ s = s -- TODO | ||||||
|  | 
 | ||||||
|  | -- Attack an entity using an item | ||||||
|  | decreaseHp :: EntityId -> ItemId -> State -> State | ||||||
|  | decreaseHp _ _ s = s | ||||||
|  | -- TODO DecreaseHp of monster | ||||||
|  | -- TODO Check if monster is dead | ||||||
|  | -- TODO Entity attack player | ||||||
|  | -- TODO Decrease durability of item | ||||||
|  | -- TODO Break item if durability below zero | ||||||
|  | 
 | ||||||
|  | -- Heal a bit | ||||||
|  | increasePlayerHp :: ItemId -> State -> State | ||||||
|  | increasePlayerHp _ s = s | ||||||
|  | -- TODO Increase playerHp | ||||||
|  | -- TODO Decrease durability of item | ||||||
|  | -- TODO Remove item if durability below zero | ||||||
|  | @ -24,14 +24,15 @@ handleInputLevelSelection = composeInputHandlers [ | ||||||
| 
 | 
 | ||||||
| -- Select a level and load it in | -- Select a level and load it in | ||||||
| selectLevel :: Game -> Game | selectLevel :: Game -> Game | ||||||
| selectLevel game@Game{ state = LevelSelection{ levelList = list, selector = selector }} = newGame | selectLevel game@Game{ state = LevelSelection list selector } = newGame | ||||||
|     where newGame      = parse $ levelFolder ++ (list !! index) |     where newGame      = parse $ levelFolder ++ (list !! index) | ||||||
|           index        = selection selector |           index        = selection selector | ||||||
| selectLevel g = g | selectLevel g = g{ state = Error "Something went wrong while selecting a level"} | ||||||
| 
 | 
 | ||||||
|  | -- TODO Lift this code from ActionSelection | ||||||
| -- Move the selector either up or down | -- Move the selector either up or down | ||||||
| moveSelector :: Direction -> Game -> Game | moveSelector :: Direction -> Game -> Game | ||||||
| moveSelector dir game@Game{ state = state@LevelSelection{ levelList = list, selector = selector } } = newGame | moveSelector dir game@Game{ state = state@(LevelSelection list selector) } = newGame | ||||||
|     where newGame      = game{ state = newState } |     where newGame      = game{ state = newState } | ||||||
|           newState     = state{ selector = newSelector } |           newState     = state{ selector = newSelector } | ||||||
|           newSelector  | constraint = selector{ selection = newSelection } |           newSelector  | constraint = selector{ selection = newSelection } | ||||||
|  | @ -41,4 +42,4 @@ moveSelector dir game@Game{ state = state@LevelSelection{ levelList = list, sele | ||||||
|           diff         | dir == North = -1 |           diff         | dir == North = -1 | ||||||
|                        | dir == South =  1 |                        | dir == South =  1 | ||||||
|                        | otherwise    =  0 |                        | otherwise    =  0 | ||||||
| moveSelector _ g = g | moveSelector _ g = g{ state = Error "Something went wrong while moving the selector up or down"} | ||||||
|  | @ -5,15 +5,16 @@ module RPGEngine.Input.Playing | ||||||
| , putCoords | , putCoords | ||||||
| ) where | ) where | ||||||
| 
 | 
 | ||||||
| import RPGEngine.Input.Core (InputHandler, handle, handleKey, composeInputHandlers) | import RPGEngine.Input.Core (InputHandler, handle, handleKey, composeInputHandlers, ListSelector (..)) | ||||||
| 
 | 
 | ||||||
| import RPGEngine.Data (Game (..), Layout(..), Level(..), Physical(..), Player(..), State(..), X, Y, Direction (..)) | import RPGEngine.Data (Game (..), Layout(..), Level(..), Physical(..), Player(..), State(..), X, Y, Direction (..), Entity (..), Item (..)) | ||||||
| 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, hasAt, filterActions, getActions) | ||||||
| 
 | 
 | ||||||
| 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(..), KeyState(..), Event(..), KeyState(..)) | import Graphics.Gloss.Interface.IO.Interact (SpecialKey(..), KeyState(..), Event(..), KeyState(..)) | ||||||
|  | import Prelude hiding (interact) | ||||||
| 
 | 
 | ||||||
| ------------------------------ Exported ------------------------------ | ------------------------------ Exported ------------------------------ | ||||||
| 
 | 
 | ||||||
|  | @ -33,10 +34,16 @@ handleInputPlaying = composeInputHandlers [ | ||||||
|     handleKey (Char 's')            Down $ movePlayer South, |     handleKey (Char 's')            Down $ movePlayer South, | ||||||
|     handleKey (Char 'a')            Down $ movePlayer West, |     handleKey (Char 'a')            Down $ movePlayer West, | ||||||
| 
 | 
 | ||||||
|     handleKey (Char 'r') Down restartGame, |     -- Interaction with entities and items | ||||||
|  |     handleKey (SpecialKey KeySpace) Down checkForInteraction, | ||||||
|  |     handleKey (Char 'f')            Down checkForInteraction, | ||||||
| 
 | 
 | ||||||
|     handleKey (Char 'i')            Down $ toggleInventoryShown True, |     handleKey (Char 'i')            Down $ toggleInventoryShown True, | ||||||
|     handleKey (Char 'i') Up   $ toggleInventoryShown False |     handleKey (Char 'i')            Up   $ toggleInventoryShown False, | ||||||
|  |     handleKey (SpecialKey KeyTab)   Down $ toggleInventoryShown True, | ||||||
|  |     handleKey (SpecialKey KeyTab)   Up   $ toggleInventoryShown False, | ||||||
|  | 
 | ||||||
|  |     handleKey (Char 'r')            Down restartGame | ||||||
|     ] |     ] | ||||||
| 
 | 
 | ||||||
| ---------------------------------------------------------------------- | ---------------------------------------------------------------------- | ||||||
|  | @ -63,6 +70,7 @@ pauseGame g = g | ||||||
| 
 | 
 | ||||||
| restartGame :: Game -> Game | restartGame :: Game -> Game | ||||||
| restartGame g@Game{ state = playing@Playing{ restart = restarted } } = g{ state = restarted } | restartGame g@Game{ state = playing@Playing{ restart = restarted } } = g{ state = restarted } | ||||||
|  | restartGame g = g{ state = Error "something went wrong while restarting the level"} | ||||||
| 
 | 
 | ||||||
| -- Go to next level if there is a next level, otherwise, initialize win state. | -- Go to next level if there is a next level, otherwise, initialize win state. | ||||||
| goToNextLevel :: State -> State | goToNextLevel :: State -> State | ||||||
|  | @ -83,16 +91,39 @@ movePlayer dir g@Game{ state = s@Playing{ player = p@Player{ position = (x, y) } | ||||||
|           newCoord  | isLegalMove dir g = (x + xD, y + yD) |           newCoord  | isLegalMove dir g = (x + xD, y + yD) | ||||||
|                     | otherwise         = (x, y) |                     | otherwise         = (x, y) | ||||||
|           (xD, yD)  = directionOffsets dir |           (xD, yD)  = directionOffsets dir | ||||||
| movePlayer _ g = g | movePlayer _ g = g{ state = Error "something went wrong while moving the player" } | ||||||
|  | 
 | ||||||
|  | checkForInteraction :: Game -> Game | ||||||
|  | checkForInteraction g@Game{ state = Playing{ level = level, player = player }} = newGame | ||||||
|  |     where newGame       | canInteract = interact g | ||||||
|  |                         | otherwise   = g | ||||||
|  |           canInteract   = not $ null $ hasAt pos level | ||||||
|  |           pos           = position player | ||||||
|  | checkForInteraction g = g{ state = Error "something went wrong while checking for entities to interact with" } | ||||||
|  | 
 | ||||||
|  | interact :: Game -> Game | ||||||
|  | interact g@Game{ state = s@Playing{ level = level, player = player } } = g{ state = newState } | ||||||
|  |     where newState   = ActionSelection actionList selector continue | ||||||
|  |           actionList = filterActions $ getActions $ fromJust $ hasAt pos level | ||||||
|  |           selector   = ListSelector 0 False | ||||||
|  |           pos        = position player | ||||||
|  |           continue   = s | ||||||
|  | interact g = g{ state = Error "something went wrong while interacting with object"} | ||||||
| 
 | 
 | ||||||
| toggleInventoryShown :: Bool -> Game -> Game | toggleInventoryShown :: Bool -> Game -> Game | ||||||
| toggleInventoryShown shown g@Game{ state = s@Playing{ player = p }}= newGame | toggleInventoryShown shown g@Game{ state = s@Playing{ player = p }}= newGame | ||||||
|     where newGame   = g{ state  = newState     } |     where newGame   = g{ state  = newState     } | ||||||
|           newState  = s{ player = newPlayer    } |           newState  = s{ player = newPlayer    } | ||||||
|           newPlayer = p{ showInventory = shown } |           newPlayer = p{ showInventory = shown } | ||||||
|  | toggleInventoryShown _ g = g{ state = Error "something went wrong while working inventory" } | ||||||
| 
 | 
 | ||||||
| -- 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 | ||||||
|     where numberedStrips = reverse $ zip [0::Int .. ] $ reverse lay |     where numberedStrips = reverse $ zip [0::Int .. ] $ reverse lay | ||||||
|           numberedList   = map (\(x, strip) -> (x, zip [0::Int ..] strip)) numberedStrips |           numberedList   = map (\(x, strip) -> (x, zip [0::Int ..] strip)) numberedStrips | ||||||
|  | 
 | ||||||
|  | -- putCoords l = concatMap numberColumns intermediate | ||||||
|  | --     where numberColumns (rowIndex, numberedRow) = map (\(colIndex, cell) -> (colIndex, rowIndex, cell)) numberedRow | ||||||
|  | --           intermediate                  = zip [0 .. ] numberedRows | ||||||
|  | --           numberedRows                  = zip [0::X .. ] $ layout l | ||||||
|  | @ -15,9 +15,11 @@ import RPGEngine.Render.Paused ( renderPaused ) | ||||||
| import RPGEngine.Render.Win ( renderWin ) | import RPGEngine.Render.Win ( renderWin ) | ||||||
| import RPGEngine.Render.Lose ( renderLose ) | import RPGEngine.Render.Lose ( renderLose ) | ||||||
| 
 | 
 | ||||||
| import Graphics.Gloss (Display) | import Graphics.Gloss ( Display, text, color ) | ||||||
| import Graphics.Gloss.Data.Picture (Picture, blank) | import Graphics.Gloss.Data.Picture (Picture, blank) | ||||||
| import Graphics.Gloss.Data.Display (Display(..)) | import Graphics.Gloss.Data.Display (Display(..)) | ||||||
|  | import RPGEngine.Render.ActionSelection (renderActionSelection) | ||||||
|  | import RPGEngine.Config (textColor) | ||||||
| 
 | 
 | ||||||
| ---------------------------------------------------------------------- | ---------------------------------------------------------------------- | ||||||
| 
 | 
 | ||||||
|  | @ -33,3 +35,5 @@ 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 Game{ state = s@ActionSelection{}} = renderActionSelection s | ||||||
|  | render Game{ state = Error message      } = color textColor $ text message | ||||||
							
								
								
									
										26
									
								
								lib/RPGEngine/Render/ActionSelection.hs
									
										
									
									
									
										Normal file
									
								
							
							
						
						
									
										26
									
								
								lib/RPGEngine/Render/ActionSelection.hs
									
										
									
									
									
										Normal file
									
								
							|  | @ -0,0 +1,26 @@ | ||||||
|  | module RPGEngine.Render.ActionSelection | ||||||
|  | ( renderActionSelection | ||||||
|  | ) where | ||||||
|  | 
 | ||||||
|  | import RPGEngine.Data (State (..), Action (..)) | ||||||
|  | import Graphics.Gloss | ||||||
|  |     ( Picture, text, pictures, translate, scale, color ) | ||||||
|  | import Graphics.Gloss.Data.Picture (blank) | ||||||
|  | import RPGEngine.Data.Level (getActionText) | ||||||
|  | import RPGEngine.Config (uizoom, selectionColor, textColor) | ||||||
|  | import RPGEngine.Input.Core (ListSelector(selection)) | ||||||
|  | import RPGEngine.Render.Playing (renderPlaying) | ||||||
|  | import RPGEngine.Render.Core (overlay) | ||||||
|  | 
 | ||||||
|  | ------------------------------ Exported ------------------------------ | ||||||
|  | 
 | ||||||
|  | renderActionSelection :: State -> Picture | ||||||
|  | renderActionSelection (ActionSelection list selector continue) = everything | ||||||
|  |     where numberedTexts = zip [0::Int ..] $ map getActionText list | ||||||
|  |           sel           = selection selector | ||||||
|  |           everything    = pictures $ [renderPlaying continue, overlay] ++ map render numberedTexts | ||||||
|  |           render (i, t) | i == sel  = color selectionColor $ make (i, t) | ||||||
|  |                         | otherwise = color textColor      $ make (i, t) | ||||||
|  |           make (i, t)   = scale uizoom uizoom $ translate 0 (offset i) $ text t | ||||||
|  |           offset i      = negate (250 * uizoom * fromIntegral i) | ||||||
|  | renderActionSelection _ = blank | ||||||
|  | @ -21,7 +21,7 @@ renderLevelSelection state = result | ||||||
| ---------------------------------------------------------------------- | ---------------------------------------------------------------------- | ||||||
| 
 | 
 | ||||||
| renderLevelList :: Renderer State | renderLevelList :: Renderer State | ||||||
| renderLevelList LevelSelection{ levelList = list, selector = selector } = everything | renderLevelList (LevelSelection list selector) = everything | ||||||
|     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 | ||||||
|  |  | ||||||
|  | @ -42,7 +42,8 @@ focusPlayer _ = id | ||||||
| renderLevel :: Renderer Level | renderLevel :: Renderer Level | ||||||
| renderLevel Level{ layout = l, items = i, entities = e } = level | renderLevel Level{ layout = l, items = i, entities = e } = level | ||||||
|     where level    = pictures [void, layout, items, entities] |     where level    = pictures [void, layout, items, entities] | ||||||
|           void     = createVoid |         --   void     = createVoid | ||||||
|  |           void     = blank | ||||||
|           layout   = renderLayout l |           layout   = renderLayout l | ||||||
|           items    = renderItems i |           items    = renderItems i | ||||||
|           entities = renderEntities e |           entities = renderEntities e | ||||||
|  |  | ||||||
|  | @ -23,6 +23,7 @@ library | ||||||
| 
 | 
 | ||||||
|     RPGEngine.Input |     RPGEngine.Input | ||||||
|     RPGEngine.Input.Core |     RPGEngine.Input.Core | ||||||
|  |     RPGEngine.Input.ActionSelection | ||||||
|     RPGEngine.Input.Menu |     RPGEngine.Input.Menu | ||||||
|     RPGEngine.Input.LevelSelection |     RPGEngine.Input.LevelSelection | ||||||
|     RPGEngine.Input.Playing |     RPGEngine.Input.Playing | ||||||
|  | @ -37,6 +38,7 @@ library | ||||||
|      |      | ||||||
|     RPGEngine.Render |     RPGEngine.Render | ||||||
|     RPGEngine.Render.Core |     RPGEngine.Render.Core | ||||||
|  |     RPGEngine.Render.ActionSelection | ||||||
|     RPGEngine.Render.Menu |     RPGEngine.Render.Menu | ||||||
|     RPGEngine.Render.LevelSelection |     RPGEngine.Render.LevelSelection | ||||||
|     RPGEngine.Render.Playing |     RPGEngine.Render.Playing | ||||||
|  |  | ||||||
							
								
								
									
										
											BIN
										
									
								
								verslag.pdf
									
										
									
									
									
								
							
							
						
						
									
										
											BIN
										
									
								
								verslag.pdf
									
										
									
									
									
								
							
										
											Binary file not shown.
										
									
								
							
		Reference in a new issue