This commit is contained in:
Tibo De Peuter 2022-12-23 12:06:46 +01:00
parent f284413836
commit 11eb00ea0b
6 changed files with 59 additions and 21 deletions

View file

@ -92,3 +92,9 @@ isInventoryFull p = inventorySize <= length (inventory p)
-- Check if the inventory of the player contains an item. -- Check if the inventory of the player contains an item.
inventoryContains :: ItemId -> Player -> Bool inventoryContains :: ItemId -> Player -> Bool
inventoryContains id p = any ((== id) . itemId) $ inventory p inventoryContains id p = any ((== id) . itemId) $ inventory p
-- Retrieve an item from inventory
itemFromInventory :: ItemId -> [Item] -> (Maybe Item, [Item])
itemFromInventory iid list = (match, filteredList)
where match = find ((== iid) . itemId) list
filteredList = filter ((/= iid) . itemId) list

View file

@ -4,11 +4,11 @@ module RPGEngine.Input.ActionSelection
import RPGEngine.Input.Core (InputHandler, handleKey, composeInputHandlers, ListSelector (selection)) import RPGEngine.Input.Core (InputHandler, handleKey, composeInputHandlers, ListSelector (selection))
import RPGEngine.Data (Game (..), State (..), Direction (..), Action (..), ItemId, EntityId, Level (..), Player (inventory, playerHp, Player), Item (..), HP) import RPGEngine.Data (Game (..), State (..), Direction (..), Action (..), ItemId, EntityId, Level (..), Player (inventory, playerHp, Player), Item (..), HP, Entity (..))
import Graphics.Gloss.Interface.IO.Game (Key(SpecialKey), SpecialKey (KeyUp, KeyDown)) import Graphics.Gloss.Interface.IO.Game (Key(SpecialKey), SpecialKey (KeyUp, KeyDown))
import Graphics.Gloss.Interface.IO.Interact import Graphics.Gloss.Interface.IO.Interact
( SpecialKey(..), KeyState(..) ) ( SpecialKey(..), KeyState(..) )
import RPGEngine.Data.Level (getWithId) import RPGEngine.Data.Level (getWithId, itemFromInventory)
import Data.Foldable (find) import Data.Foldable (find)
------------------------------ Exported ------------------------------ ------------------------------ Exported ------------------------------
@ -72,13 +72,30 @@ useItem :: ItemId -> State -> State -- TODO
useItem _ s = s -- TODO useItem _ s = s -- TODO
-- Attack an entity using an item -- Attack an entity using an item
-- Should receive a Playing state
decreaseHp :: EntityId -> ItemId -> State -> State decreaseHp :: EntityId -> ItemId -> State -> State
decreaseHp _ _ s = s decreaseHp eid iid s@Playing{ level = level, player = player } = newState
-- TODO DecreaseHp of monster where newState = s{ level = newLevel, player = newPlayer }
-- TODO Check if monster is dead -- Change player
-- TODO Entity attack player (Just usingItem) = find ((== iid) . itemId) (inventory player)
-- TODO Decrease durability of item usedItem = decreaseDurability usingItem
-- TODO Break item if durability below zero newInventory = filter (/= usingItem) $ inventory player
newPlayer = player{ inventory = putItemBack usedItem newInventory, playerHp = newHp }
putItemBack Nothing inv = inv
putItemBack (Just item) inv = item:inv
newHp = changeHealth (playerHp player) damageGetAmount -- Damage dealt by entity
damageDealAmount = itemValue usingItem
-- Change entity
(Just (Right attackedEntity)) = getWithId eid level
newLevel = level{ entities = putEntityBack dealtWithEntity newEntities }
newEntities = filter ((/= eid) . entityId) $ entities level
dealtWithEntity = decreaseHealth attackedEntity damageDealAmount
putEntityBack Nothing list = list
putEntityBack (Just ent) list = ent:list
damageGetAmount = inverse (entityValue attackedEntity)
inverse (Just val) = Just (-val)
inverse Nothing = Nothing
decreaseHp _ _ _ = Error "something went wrong while attacking"
-- Heal a bit -- Heal a bit
-- Should receive a Player -- Should receive a Player
@ -97,6 +114,12 @@ decreaseDurability item@Item{ useTimes = Nothing } = Just item -- Infinite uses
decreaseDurability item@Item{ useTimes = Just val } | 0 < val - 1 = Just item{ useTimes = Just (val - 1) } decreaseDurability item@Item{ useTimes = Just val } | 0 < val - 1 = Just item{ useTimes = Just (val - 1) }
| otherwise = Nothing -- Broken | otherwise = Nothing -- Broken
decreaseHealth :: Entity -> Maybe Int -> Maybe Entity
decreaseHealth entity@Entity{ entityHp = Nothing } _ = Just entity
decreaseHealth entity@Entity{ entityHp = Just val } (Just i) | 0 < val - i = Just entity{ entityHp = Just (val - i) }
| otherwise = Nothing
decreaseHealth entity _ = Just entity
-- Change given health by a given amount -- Change given health by a given amount
changeHealth :: HP -> HP -> HP changeHealth :: HP -> HP -> HP
changeHealth (Just health) (Just difference) = Just (health + difference) changeHealth (Just health) (Just difference) = Just (health + difference)

View file

@ -139,7 +139,7 @@ action = try $ do
let answer | script == "leave" = Leave let answer | script == "leave" = Leave
| script == "retrieveItem" = RetrieveItem arg | script == "retrieveItem" = RetrieveItem arg
| script == "useItem" = UseItem arg | script == "useItem" = UseItem arg
| script == "decreaseHp" = DecreaseHp first second | script == "decreaseHp" = DecreaseHp first (filter (/= ' ') second) -- TODO Work this hack away
| script == "increasePlayerHp" = IncreasePlayerHp arg | script == "increasePlayerHp" = IncreasePlayerHp arg
| otherwise = DoNothing | otherwise = DoNothing
(first, ',':second) = break (== ',') arg (first, ',':second) = break (== ',') arg

View file

@ -1,4 +1,4 @@
import RPGEngine import RPGEngine ( playRPGEngine )
----------------------------- Constants ------------------------------ ----------------------------- Constants ------------------------------

View file

@ -6,7 +6,6 @@ import RPGEngine.Data
import RPGEngine.Parse.Core import RPGEngine.Parse.Core
import RPGEngine.Parse.TextToStructure import RPGEngine.Parse.TextToStructure
import RPGEngine.Parse.StructureToGame import RPGEngine.Parse.StructureToGame
import RPGEngine.Parse.TextToStructure (gameFile)
spec :: Spec spec :: Spec
spec = do spec = do
@ -142,6 +141,12 @@ spec = do
Right struct = parseWith structure input Right struct = parseWith structure input
structureToActions struct `shouldBe` correct structureToActions struct `shouldBe` correct
it "DecreaseHp(entityid, itemid)" $ do
let input = "{ [] decreaseHp(devil, sword) }"
correct = [([], DecreaseHp "devil" "sword")]
Right struct = parseWith structure input
structureToActions struct `shouldBe` correct
describe "Entities" $ do describe "Entities" $ do
it "Simple entity" $ do it "Simple entity" $ do
pendingWith "still need to write this" pendingWith "still need to write this"

View file

@ -150,6 +150,10 @@ spec = do
correct = Right $ Regular $ Action $ DecreaseHp "entityId" "objectId" correct = Right $ Regular $ Action $ DecreaseHp "entityId" "objectId"
parseWith regular input `shouldBe` correct parseWith regular input `shouldBe` correct
let input = "decreaseHp(entityId,objectId)"
correct = Right $ Regular $ Action $ DecreaseHp "entityId" "objectId"
parseWith regular input `shouldBe` correct
let input = "increasePlayerHp(objectId)" let input = "increasePlayerHp(objectId)"
correct = Right $ Regular $ Action $ IncreasePlayerHp "objectId" correct = Right $ Regular $ Action $ IncreasePlayerHp "objectId"
parseWith regular input `shouldBe` correct parseWith regular input `shouldBe` correct