#4 Setup interaction
This commit is contained in:
parent
ef784c2dbc
commit
9addf1ed07
13 changed files with 223 additions and 33 deletions
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
|
||||
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)
|
||||
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
|
||||
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 }
|
||||
newState = state{ selector = newSelector }
|
||||
newSelector | constraint = selector{ selection = newSelection }
|
||||
|
@ -41,4 +42,4 @@ moveSelector dir game@Game{ state = state@LevelSelection{ levelList = list, sele
|
|||
diff | dir == North = -1
|
||||
| dir == South = 1
|
||||
| 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
|
||||
) 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.Level (directionOffsets, findFirstOf)
|
||||
import RPGEngine.Data.Level (directionOffsets, findFirstOf, hasAt, filterActions, getActions)
|
||||
|
||||
import Data.Maybe (fromJust, isNothing)
|
||||
import Graphics.Gloss.Interface.IO.Game (Key(..))
|
||||
import Graphics.Gloss.Interface.IO.Interact (SpecialKey(..), KeyState(..), Event(..), KeyState(..))
|
||||
import Prelude hiding (interact)
|
||||
|
||||
------------------------------ Exported ------------------------------
|
||||
|
||||
|
@ -28,15 +29,21 @@ handleInputPlaying = composeInputHandlers [
|
|||
handleKey (SpecialKey KeyDown) Down $ movePlayer South,
|
||||
handleKey (SpecialKey KeyLeft) Down $ 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 'w') Down $ movePlayer North,
|
||||
handleKey (Char 'd') Down $ movePlayer East,
|
||||
handleKey (Char 's') Down $ movePlayer South,
|
||||
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') Up $ toggleInventoryShown False
|
||||
handleKey (Char 'i') Down $ toggleInventoryShown True,
|
||||
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 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.
|
||||
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)
|
||||
| otherwise = (x, y)
|
||||
(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 shown g@Game{ state = s@Playing{ player = p }}= newGame
|
||||
where newGame = g{ state = newState }
|
||||
newState = s{ player = newPlayer }
|
||||
newPlayer = p{ showInventory = shown }
|
||||
toggleInventoryShown _ g = g{ state = Error "something went wrong while working inventory" }
|
||||
|
||||
-- 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 = 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
|
Reference in a new issue