Skip to content

Commit

Permalink
use multiple perception to determine if a monster sees a particular hero
Browse files Browse the repository at this point in the history
  • Loading branch information
Mikolaj committed Mar 22, 2011
1 parent 23ad4e2 commit b39b854
Show file tree
Hide file tree
Showing 2 changed files with 39 additions and 17 deletions.
22 changes: 22 additions & 0 deletions src/Perception.hs
Expand Up @@ -3,6 +3,8 @@ module Perception where
import qualified Data.Set as S
import Data.List as L
import qualified Data.IntMap as IM
import Data.Maybe
import Control.Monad

import Geometry
import State
Expand All @@ -28,6 +30,26 @@ ptreachable = preachable . ptotal
ptvisible :: Perceptions -> S.Set Loc
ptvisible = pvisible . ptotal

actorSeesLoc :: Actor -> Loc -> Perceptions -> Actor -> Bool
actorSeesLoc actor loc per pl =
let tryHero = case actor of
AMonster _ -> Nothing
AHero i -> do
hper <- IM.lookup i (pheroes per)
return $ loc `S.member` (pvisible hper)
tryPl = do -- the case for a monster under player control
guard $ actor == pl
pper <- pplayer per
return $ loc `S.member` pvisible pper
tryAny = tryHero `mplus` tryPl
in fromMaybe False tryAny -- assume not visible, if no perception found

-- Not quite correct if FOV not symmetric (Shadow).
actorSeesActor :: Actor -> Actor -> Loc -> Loc -> Perceptions -> Actor -> Bool
actorSeesActor actor1 actor2 loc1 loc2 per pl =
actorSeesLoc actor1 loc2 per pl ||
actorSeesLoc actor2 loc1 per pl

perception_ :: State -> Perceptions
perception_ state@(State { slevel = Level { lmap = lmap, lheroes = hs },
sconfig = config,
Expand Down
34 changes: 17 additions & 17 deletions src/StrategyState.hs
Expand Up @@ -4,6 +4,7 @@ import Data.List as L
import Data.Map as M
import Data.Set as S
import qualified Data.IntMap as IM
import Data.Maybe

import Geometry
import Level
Expand All @@ -17,7 +18,8 @@ import State

strategy :: Actor -> State -> Perceptions -> Strategy Dir
strategy actor
state@(State { stime = time,
state@(State { splayer = pl,
stime = time,
slevel = Level { lsmell = nsmap,
lmap = lmap } })
per =
Expand All @@ -27,38 +29,36 @@ strategy actor
Nose -> nose
_ -> onlyAccessible moveRandomly
where
-- TODO: we check if the monster is visible by the hero rather than
-- if the hero is visible by the monster -- this is more efficient, but
-- is not correct with the Shadow FOV (the other FOVs are symmetrical)
-- TODO: set monster targets and then prefer targets to other heroes
Movable { mtype = mt, mloc = me, mdir = mdir } = getActor state actor
delState = deleteActor actor state
hs = levelHeroList delState
ms = levelMonsterList delState
hs = L.map (\ (i, m) -> (AHero i, mloc m)) $
IM.assocs $ lheroes $ slevel delState
ms = L.map (\ (i, m) -> (AMonster i, mloc m)) $
IM.assocs $ lmonsters $ slevel delState
-- If no heroes on the level, monsters go at each other. TODO: let them
-- earn XP by killing each other to make this dangerous to the player.
enemyLocs = L.map mloc $ if L.null hs then ms else hs
enemyDist = L.sort $ L.map (\ l -> (distance (me, l), l)) enemyLocs
lmh = if L.null hs then ms else hs
lmhVisible = L.filter (\ (a, l) -> actorSeesActor a actor l me per pl) lmh
lmhDist = L.map (\ (_, l) -> (distance (me, l), l)) lmhVisible
-- Below, "player" is the hero (or a monster, if no heroes on this level)
-- chased by the monster ("ploc" is his location, etc.).
-- As soon as the monster hits, this hero becomes really the currently
-- selected hero.
-- We have to sort the list to avoid bias towards the currently selected
-- hero; instead monsters will prefer heroes with smaller locations.
ploc = case enemyDist of
[] -> Nothing
(_, ploc) : _ -> Just ploc
-- As soon as the monster hits, the hero becomes really the currently
-- player-controlled hero.
ploc = case lmhVisible of
[] -> Nothing
_ -> Just $ snd $ L.minimum lmhDist
-- TODO: currently even invisible heroes are targeted if _any_ hero
-- is visible; each hero should carry his own perception to check
-- if he's visible by a given monster
playerVisible = me `S.member` ptvisible per -- monster sees any hero
playerVisible = isJust ploc -- monster sees any hero
playerAdjacent = maybe False (adjacent me) ploc
towardsPlayer = maybe (0, 0) (\ ploc -> towards (me, ploc)) ploc
onlyTowardsPlayer = only (\ x -> distance (towardsPlayer, x) <= 1)
lootPresent = (\ x -> not $ L.null $ titems $ lmap `at` x)
onlyLootPresent = onlyMoves lootPresent me
onlyPreservesDir = only (\ x -> maybe True (\ d -> distance (neg d, x) > 1) mdir)
onlyUnoccupied = onlyMoves (unoccupied ms) me
onlyUnoccupied = onlyMoves (unoccupied (levelMonsterList delState)) me
onlyAccessible = onlyMoves (accessible lmap me) me
-- Monsters don't see doors more secret than that. Enforced when actually
-- opening doors, too, so that monsters don't cheat.
Expand Down

0 comments on commit b39b854

Please sign in to comment.