module GameLogic where import GameTypes import Control.Lens import Linear import Data.Maybe import Data.Char import qualified Data.Map as M {- * Initialization -} -- | Generates a world with the hero and an endboss at a specific positions -- in a dungeon with a specific size. newWorldWithBoss :: V2 Integer -> V2 Integer -> (Integer, Integer) -> World -- XXX: ??! This looks very ugly. What does it even do? Some refactoring should be done. Also, use record syntax to make things clear.. newWorldWithBoss hPos mPos size = entities.at mPos._Just .~ Boss (Stats West 500) $ entities.at hPos ?~ Hero (Stats East 100) $ World Active 0 (walls (atBorder size) $ M.fromList $ map (flip (,) Floor) $ V2 <$> [0..(size^._1)] <*> [0..(size^._2)]) hPos -- | Creates a new bomb with a certain life time and orientation. newBomb :: Integer -> Direction -> Entity newBomb l d = Bomb (Stats d l) -- | Creates a new small fire fire :: Entity fire = Fire (Stats North 1) -- | Creates a new big fire. bigFire :: Entity bigFire = Fire (Stats North 3) -- | Tests whether a position is on the edge of the map. atBorder :: (Integer,Integer) -> Position -> Bool atBorder (bx,by) (V2 x y) = x `elem` [bx,0] || y `elem` [by,0] -- | Places walls on the edge of the dungeon map. walls :: (V2 Integer -> Bool) -> Dungeon -> Dungeon walls test = M.mapWithKey (\pos c -> if test pos then Wall else c) {- * Game logic -} -- | Performs an action on the game state (world). performAction :: World -> Action -> World performAction w a = case (w^.mode,a) of (Active,Move dir) -> updateWorld.moveHero (toVector dir) $ w (Active,Attack) -> updateWorld.attack $ w (Active,SetTrap) -> w -- TODO setTrap... (Active,Pause) -> mode.~Paused $ w (Paused,Pause) -> mode.~Active $ w _ -> w -- | Updates the all the entities in the world by calling the function updateDungeon -- and registers a game turn. updateWorld :: World -> World updateWorld = updateDungeon.count where count = turn +~ 1 -- | Updates all the entities in the dungeon. updateDungeon :: World -> World updateDungeon w = M.foldrWithKey updateEnt w (w^.entities) where updateEnt pos ent = case ent of Bomb s | s^.life.to (<=0) -> explodeBomb pos | otherwise -> moveBomb pos (s^.orient.to toVector) Fire s | s^.life.to (<=0) -> entities %~ M.insert pos Floor | otherwise -> entities.at pos._Just._Fire.life -~ 1 Boss s | s^.life.to (<=0) -> (mode .~ Ended) . (entities %~ M.insert pos (Boss s )) | otherwise -> updateBoss pos Hero s | s^.life.to (<=0) -> (mode .~ Ended) . (entities %~ M.insert pos (Hero s )) | otherwise -> id _ -> id -- | Updates the boss at a given position. The bosses behavior depends on the turn counter. -- Generally the boss tries to approach the hero and attack him by throwing bombs at him. updateBoss :: Position -> World -> World updateBoss pos w = let atHero = badAiming $ w^.heroPos - pos spawnPos = pos + atHero withRandomTimer = w^.turn.to (\t -> 2 + (1 + mod t 5)*(1 + mod t 3)) in case w^.turn.to (`mod` 16) of 0 -> moveBoss pos (V2 1 0) w 1 -> moveBoss pos atHero w 2 -> throwBomb spawnPos withRandomTimer atHero w 3 -> w 4 -> moveBoss pos (negate atHero) w 5 -> moveBoss pos (V2 (-1) 0) w 6 -> moveBoss pos (V2 0 (-1)) w 7 -> throwBomb spawnPos withRandomTimer atHero w 8 -> moveBoss pos (negate atHero) w 9 -> moveBoss pos atHero w 10 -> moveBoss pos (V2 0 1) w 11 -> moveBoss pos atHero w 12 -> moveBoss pos atHero w 13 -> moveBoss pos atHero w 14 -> moveBoss pos atHero w 15 -> throwBomb spawnPos withRandomTimer atHero w _ -> w -- | Calculates the approximate direction of the hero. badAiming :: V2 Integer -> V2 Integer badAiming relPos = case relPos^._x.to (abs) < relPos^._y.to (abs) of True -> signum relPos & _x .~ 0 False -> signum relPos & _y .~ 0 -- | If possible, this function moves the hero into a given direction by calling the function moveFrom. -- Otherwise, only the orientation is changed towards the intended direction of movement. moveHero :: DirVector -> World -> World moveHero dir w = let pos = w^.heroPos aim = pos + dir in case w^.entities.at aim of Just Floor -> w & heroPos .~ aim & entities %~ moveFrom pos dir Just (Fire _) -> w & heroPos .~ aim & entities.at pos._Just._Hero.life -~ 10 & entities %~ moveFrom pos dir -- XXX magic number.. issue: implement damage system _ -> w & entities.at pos._Just.stats.orient .~ (fromVector dir) -- | If possible, this function moves the boss into a given direction by calling the function moveFrom. -- Otherwise, only the orientation is changed towards the intended direction of movement. moveBoss :: Position -> DirVector -> World -> World moveBoss pos dir w = let aim = pos + dir in case w^.entities.at aim of Just Floor -> w & entities %~ moveFrom pos dir Just Trap -> w -- TODO setTrap... _ -> w & entities.at pos._Just.stats.orient .~ (fromVector dir) -- | If possible, this function moves a bomb at a given position into a given direction -- by calling the function moveFrom. Otherwise, the bomb explodes. moveBomb :: Position -> DirVector -> World -> World moveBomb pos dir w = let aim = pos + dir in case w^.entities.at aim of Just Floor -> w & entities %~ moveFrom pos dir Just (Fire s) | s^.life < 2 -> w & entities %~ moveFrom pos dir | otherwise -> w & explodeBomb pos _ -> w & explodeBomb pos -- | Moves any movable entity with at a given position into a given direction. moveFrom :: Position -> DirVector -> Dungeon -> Dungeon moveFrom p d dungeon = case dungeon^.at p of Just (Hero s) -> M.insert (p+d) (Hero (s & orient .~ fromVector d)) $ M.insert p Floor dungeon Just (Bomb s) -> M.insert (p+d) (Bomb (s & life -~ 1)) $ M.insert p Floor dungeon Just (Boss s) -> M.insert (p+d) (Boss (s & orient .~ fromVector d)) $ M.insert p Floor dungeon _ -> dungeon -- | Attacks the location in front of the hero. Erases fires, harms enemies. attack :: World -> World attack w = let pos = w^.heroPos maybeAim = w^.entities.at pos^?_Just.stats.orient.to ((pos +).toVector) in case maybeAim >>= \aim -> (,) aim <$> w^.entities.at aim of Just (aim,Boss s) -> w & entities.at aim._Just._Boss.life -~ 45 -- XXX magic number.. issue: implement damage system Just (aim,Fire _) -> w & entities %~ M.insert aim Floor _ -> w -- | Sets a trap in front of the hero, that harms enemies if stepped on. setTrap :: World -> World setTrap w = w -- TODO setTrap... -- | Creates a bomb at a given position with specific detonation delay and orientation. throwBomb :: Position -> Integer -> DirVector -> World -> World throwBomb pos delay dir w = case w^.entities.at pos of Just Floor -> w & entities %~ M.insert pos (newBomb delay $ fromVector dir) _ -> w & explodeBomb pos -- | Creates a big fire at a given position and eight small fires adjacent to that position. -- If the hero is at one of these positions he gets damaged. explodeBomb :: Position -> World -> World explodeBomb p w = foldr maybeSetFire w (around p) where maybeSetFire pos w' = case w'^.entities.at pos of Just (Bomb _) | pos==p -> w' & entities %~ M.insert pos bigFire | otherwise -> w' & entities %~ M.insert pos bigFire & explodeBomb pos Just Floor -> w' & entities %~ M.insert pos fire Just (Hero s) | pos==p -> w' & entities %~ M.insert pos (Hero (s & life -~ 30)) -- XXX magic number.. issue: implement damage system | otherwise -> w' & entities %~ M.insert pos (Hero (s & life -~ 10)) -- XXX magic number.. issue: implement damage system _ -> w' -- | Calculates the adjacent positions of a given position around :: Position -> [Position] around pos = (+pos) <$> (V2 <$> [-1..1] <*> [-1..1])