Skip to content

Commit

Permalink
add "last seen at" field to enemy target
Browse files Browse the repository at this point in the history
  • Loading branch information
Mikolaj committed Apr 8, 2011
1 parent ea4a7e1 commit 6a595a9
Show file tree
Hide file tree
Showing 4 changed files with 33 additions and 34 deletions.
12 changes: 6 additions & 6 deletions src/Actions.hs
Expand Up @@ -86,7 +86,7 @@ endTargeting accept = do
cloc <- gets (clocation . scursor)
lvlSwitch returnLn -- return to the original level of the player
modify (updateCursor (\ c -> c { ctargeting = False }))
let isEnemy = case target of TEnemy _ -> True ; _ -> False
let isEnemy = case target of TEnemy _ _ -> True ; _ -> False
when (not isEnemy) $
if accept
then updatePlayerBody (\ p -> p { mtarget = TLoc cloc })
Expand All @@ -100,7 +100,7 @@ endTargetingMsg = do
state <- get
let verb = "target"
targetMsg = case target of
TEnemy a ->
TEnemy a _ll ->
case findActorAnyLevel a state of
Just (_, m) -> objectMovable (mkind m)
Nothing -> "a long gone adversary"
Expand Down Expand Up @@ -437,8 +437,8 @@ targetMonster = do
target <- gets (mtarget . getPlayerBody)
targeting <- gets (ctargeting . scursor)
let i = case target of
TEnemy (AMonster n) | targeting -> n -- try next monster
TEnemy (AMonster n) -> n - 1 -- try to retarget old monster
TEnemy (AMonster n) _ | targeting -> n -- try next monster
TEnemy (AMonster n) _ -> n - 1 -- try to retarget old monster
_ -> -1 -- try to target first monster (e.g., number 0)
dms = case pl of
AMonster n -> IM.delete n ms -- don't target yourself
Expand All @@ -448,7 +448,7 @@ targetMonster = do
lf = L.filter (\ (_, m) -> actorSeesLoc pl (mloc m) per pl) gtlt
tgt = case lf of
[] -> target -- no monsters in sight, stick to last target
(ni, _) : _ -> TEnemy (AMonster ni) -- pick the next monster
(ni, nm) : _ -> TEnemy (AMonster ni) (mloc nm) -- pick the next
updatePlayerBody (\ p -> p { mtarget = tgt })
setCursor tgt

Expand Down Expand Up @@ -485,7 +485,7 @@ doLook =
Nothing -> ""
else ""
mode = case target of
TEnemy _ -> "[targeting monster] "
TEnemy _ _ -> "[targeting monster] "
TLoc _ -> "[targeting location] "
TCursor -> "[targeting current] "
-- general info about current loc
Expand Down
10 changes: 5 additions & 5 deletions src/Movable.hs
Expand Up @@ -65,19 +65,19 @@ instance Binary Actor where
_ -> fail "no parse (Actor)"

data Target =
TEnemy Actor -- ^ fire at the actor (a monster or a hero)
| TLoc Loc -- ^ fire at a given location
| TCursor -- ^ fire at the current position of the cursor; the default
TEnemy Actor Loc -- ^ fire at the actor; last seen location
| TLoc Loc -- ^ fire at a given location
| TCursor -- ^ fire at the current position of the cursor; default
deriving (Show, Eq)

instance Binary Target where
put (TEnemy a) = putWord8 0 >> put a
put (TEnemy a ll) = putWord8 0 >> put a >> put ll
put (TLoc loc) = putWord8 1 >> put loc
put TCursor = putWord8 2
get = do
tag <- getWord8
case tag of
0 -> liftM TEnemy get
0 -> liftM2 TEnemy get get
1 -> liftM TLoc get
2 -> return TCursor
_ -> fail "no parse (Target)"
2 changes: 1 addition & 1 deletion src/MovableState.hs
Expand Up @@ -64,7 +64,7 @@ targetToLoc visible state =
if lname (slevel state) == clocLn (scursor state)
then Just $ clocation (scursor state)
else Nothing -- cursor invalid: set at a different level
TEnemy a -> do
TEnemy a _ll -> do
guard $ memActor a state -- alive and on the current level?
let loc = mloc (getActor a state)
guard $ S.member loc visible -- visible?
Expand Down
43 changes: 21 additions & 22 deletions src/StrategyState.hs
Expand Up @@ -48,30 +48,35 @@ strategy actor
IM.assocs $ lheroes $ slevel delState
ms = L.map (\ (i, m) -> (AMonster i, mloc m)) $
IM.assocs $ lmonsters $ slevel delState
-- Below, "foe" is the hero (or a monster) at floc, attacked by the actor.
-- Below, "foe" is the hero (or a monster, or loc), followed by the actor.
(newTgt, floc) =
case tgt of
TEnemy a | focusedMonster ->
TEnemy a ll | focusedMonster ->
case findActorAnyLevel a delState of
Just (_, m) ->
let l = mloc m
in if actorReachesActor a actor l me per pl
then (tgt, Just l)
else closest -- TODO: got to the last know location
in -- We assume monster sight is infravision.
if actorReachesActor a actor l me per pl
then (TEnemy a l, Just l)
else if isJust (snd closest) || me == ll
then closest -- prefer visible enemies
else (tgt, Just ll) -- last known location of enemy
Nothing -> closest -- enemy dead
TLoc loc -> (tgt, Just loc) -- ignore everything and go to loc
TLoc loc -> if me == loc
then closest
else (tgt, Just loc) -- ignore everything and go to loc
_ -> closest
closest =
let foes = if L.null hs then ms else hs
-- We assume monster sight is infravision, so light has no effect.
-- We assume monster sight is infravision, so light has no effect.
foeVisible =
L.filter (\ (a, l) -> actorReachesActor a actor l me per pl) foes
foeDist = L.map (\ (a, l) -> (distance (me, l), l, a)) foeVisible
-- Below, "foe" is the hero (or a monster) at floc, attacked by the actor.
in case foeDist of
[] -> (tgt, Nothing)
[] -> (TCursor, Nothing)
_ -> let (_, l, a) = L.minimum foeDist
in (TEnemy a, Just $ l)
in (TEnemy a l, Just l)
onlyFoe = onlyMoves (maybe (const False) (==) floc) me
towardsFoe = case floc of
Nothing -> const mzero
Expand All @@ -96,14 +101,13 @@ strategy actor
L.sortBy (\ (_, s1) (_, s2) -> compare s2 s1) $
L.filter (\ (_, s) -> s > 0) $
L.map (\ x -> (x, nsmap ! (me `shift` x) - time `max` 0)) moves
fromDir d = dirToAction actor `liftM` onlySensible d
fromFoe d = setTarget actor newTgt `liftM` fromDir d
fromDir d = dirToAction actor newTgt `liftM` onlySensible d

strategy =
fromDir (onlyTraitor moveFreely) -- traitor disguised; hard to target
.| fromFoe (onlyFoe moveFreely)
fromDir (onlyTraitor moveFreely) -- traitor has priority
.| fromDir (onlyFoe moveFreely)
.| (greedyMonster && lootHere me) .=> actionPickup
.| fromFoe moveTowards
.| fromDir moveTowards
.| lootHere me .=> actionPickup
.| fromDir moveAround
actionPickup = return $ actorPickupItem actor
Expand All @@ -121,21 +125,16 @@ strategy actor
.| niq mk > 5 .=> onlyKeepsDir 2 moveRandomly
.| moveRandomly

dirToAction :: Actor -> Dir -> Action ()
dirToAction actor dir =
dirToAction :: Actor -> Target -> Dir -> Action ()
dirToAction actor tgt dir =
assert (dir /= (0,0)) $ do
-- set new direction
updateAnyActor actor $ \ m -> m { mdir = Just dir }
updateAnyActor actor $ \ m -> m { mdir = Just dir, mtarget = tgt }
-- perform action
tryWith (advanceTime actor) $
-- if the following action aborts, we just advance the time and continue
moveOrAttack True True actor dir

setTarget :: Actor -> Target -> Action () -> Action ()
setTarget actor tgt action = do
modify (updateAnyActorBody actor (\ m -> m { mtarget = tgt }))
action

onlyMoves :: (Dir -> Bool) -> Loc -> Strategy Dir -> Strategy Dir
onlyMoves p l = only (\ x -> p (l `shift` x))

Expand Down

0 comments on commit 6a595a9

Please sign in to comment.