Skip to content

Commit

Permalink
code naming convention: "player" is the currently selected hero
Browse files Browse the repository at this point in the history
This is short form of "player-controlled hero".
Other heroes and all heroes in general are just "heroes".
  • Loading branch information
Mikolaj committed Jan 31, 2011
1 parent de20d76 commit 081101a
Show file tree
Hide file tree
Showing 9 changed files with 76 additions and 74 deletions.
42 changes: 21 additions & 21 deletions src/Actions.hs
Expand Up @@ -153,7 +153,7 @@ remember =
modify (updateLevel (updateLMap (\ lmap -> foldr rememberLoc lmap vis)))

checkHeroDeath :: Action ()
checkHeroDeath = -- TODO: for now, quit only when the last hero dies.
checkHeroDeath = -- TODO: for now, quit only when the last hero dies. TODO: check if it should have Hero or Player in the name (is it about the current hero?)
do
player <- gets splayer
let php = mhp player
Expand Down Expand Up @@ -288,49 +288,49 @@ fleeDungeon =
-- TODO: extend to number keys switching to heroes on any levels.
cycleHero =
do
pls <- gets (lplayers . slevel)
hs <- gets (lheroes . slevel)
nln <- gets (lname . slevel)
player <- gets splayer
look <- gets slook
case look of
Just look@(Look { returnLn = ln })
| ln /= nln ->
case IM.assocs pls of
case IM.assocs hs of
[] -> abortWith "No heroes on this level."
(ni, np) : _ ->
do
let i = playerNumber player
let i = heroNumber player
ins = IM.insert i player
pli = updatePlayers ins
pli = updateHeroes ins
del = IM.delete ni
modify (updateDungeon (updateDungeonLevel pli ln))
modify (updateLevel (updatePlayers del))
modify (updateLevel (updateHeroes del))
modify (updatePlayer (const np))
modify (updateLook (const (Just $ look { returnLn = nln })))
messageAdd "A hero selected."
_ ->
let i = playerNumber player
(lt, gt) = IM.split i pls
let i = heroNumber player
(lt, gt) = IM.split i hs
in case IM.assocs gt ++ IM.assocs lt of
[] -> abortWith "Only one hero on this level."
(ni, np) : _ ->
do
swapCurrentHero (ni, np)
messageAdd "Next hero selected."

swapCurrentHero :: (Int, Player) -> Action ()
swapCurrentHero :: (Int, Hero) -> Action ()
swapCurrentHero (ni, np) =
do
player <- gets splayer
let i = playerNumber player
upd pls = IM.insert i player $ IM.delete ni pls
let i = heroNumber player
upd hs = IM.insert i player $ IM.delete ni hs
when (ni == i) abort
modify (updateLevel (updatePlayers upd))
modify (updateLevel (updateHeroes upd))
modify (updatePlayer (const np))

-- | Calculate loot's worth. TODO: move to another module, and refine significantly. TODO: calculate for all players on the current level.
calculateTotal :: Player -> Int
calculateTotal player = L.sum $ L.map price $ mitems player
-- | Calculate loot's worth. TODO: move to another module, and refine significantly. TODO: calculate for all heroes on the current level.
calculateTotal :: Hero -> Int
calculateTotal hero = L.sum $ L.map price $ mitems hero
where
price i = if iletter i == Just '$' then icount i else 10 * icount i

Expand Down Expand Up @@ -601,7 +601,7 @@ displayItems msg sorted is =
overlay ovl

-- | This function performs a move (or attack) by any actor, i.e., it can handle
-- both monsters and the player.
-- both monsters and the player (the currently selected hero).
moveOrAttack :: Bool -> -- allow attacks?
Bool -> -- auto-open doors on move
Actor -> -- who's moving?
Expand All @@ -623,16 +623,16 @@ moveOrAttack allowAttacks autoOpen actor dir
s = lmap `at` loc -- tile at current location
nloc = loc `shift` dir -- target location
t = lmap `at` nloc -- tile at target location
ps = levelHeroAssocs state
attPlayer = find (\ (_, m) -> mloc m == nloc) ps
attackedPlayer = if isJust attPlayer then [APlayer] else []
hs = levelHeroAssocs state
attHero = find (\ (_, m) -> mloc m == nloc) hs
attackedHero = if isJust attHero then [APlayer] else []
attMonsters = findIndices (\ m -> mloc m == nloc) monsters
attackedMonsters = L.map AMonster $ attMonsters
attacked :: [Actor]
attacked = attackedPlayer ++ attackedMonsters
attacked = attackedHero ++ attackedMonsters
-- Focus on the attacked hero, if any.
-- TODO: This requires a special case if a hero bumps into another.
maybe (return ()) swapCurrentHero attPlayer
maybe (return ()) swapCurrentHero attHero
-- At the moment, we check whether there is a monster before checking accessibility
-- i.e., we can attack a monster on a blocked location. For instance,
-- a monster on an open door can be attacked diagonally, and a
Expand Down
2 changes: 1 addition & 1 deletion src/Display2.hs
Expand Up @@ -142,7 +142,7 @@ displayLevel session per
(state@(State { splayer = player@(Monster { mhpmax = phpmax, mhp = php, mdir = pdir, mloc = ploc }),
stime = time,
sassocs = assocs,
slevel = lvl@(Level nm pls sz@(sy,sx) ms smap nlmap lmeta) }))
slevel = lvl@(Level nm hs sz@(sy,sx) ms smap nlmap lmeta) }))
msg moverlay =
let
overlay = maybe "" id moverlay
Expand Down
8 changes: 4 additions & 4 deletions src/Dungeon.hs
Expand Up @@ -327,16 +327,16 @@ addMonster state@(State { slevel = lvl@(Level { lmonsters = ms,
return (updateMonsters (const (m : ms)) lvl)
else return lvl

-- | Create a new hero in the level, close to the current player.
-- | Create a new hero in the level, close to the player.
addHero :: Int -> State -> Int -> Rnd State
addHero hp state@(State { splayer = player,
slevel = lvl@(Level { lmonsters = ms }) }) n =
slevel = lvl@(Level { lmonsters = ms }) }) n =
do
let hs = levelHeroList state
ploc <- findLocTry 10000 lvl -- TODO: bad for large levels
(\ l t -> open t
&& not (l `L.elem` L.map mloc (hs ++ ms)))
(\ l t -> floor t
&& distance (mloc player, l) < 5 + L.length hs `div` 3)
let hero = defaultPlayer n ploc hp
return (updateLevel (updatePlayers (IM.insert n hero)) state)
let hero = defaultHero n ploc hp
return (updateLevel (updateHeroes (IM.insert n hero)) state)
16 changes: 8 additions & 8 deletions src/Grammar.hs
Expand Up @@ -9,22 +9,22 @@ import ItemState

-- | How to refer to a monster in object position of a sentence.
objectMonster :: MonsterType -> String
objectMonster (Player _) = "you"
objectMonster Eye = "the reducible eye"
objectMonster FastEye = "the super-fast eye"
objectMonster Nose = "the point-free nose"
objectMonster (Hero _) = "you"
objectMonster Eye = "the reducible eye"
objectMonster FastEye = "the super-fast eye"
objectMonster Nose = "the point-free nose"

-- | How to refer to a monster in subject position of a sentence.
subjectMonster :: MonsterType -> String
subjectMonster x = let (s:r) = objectMonster x in toUpper s : r

verbMonster :: MonsterType -> String -> String
verbMonster (Player _) v = v
verbMonster _ v = v ++ "s"
verbMonster (Hero _) v = v
verbMonster _ v = v ++ "s"

compoundVerbMonster :: MonsterType -> String -> String -> String
compoundVerbMonster (Player _) v p = v ++ " " ++ p
compoundVerbMonster _ v p = v ++ "s " ++ p
compoundVerbMonster (Hero _) v p = v ++ " " ++ p
compoundVerbMonster _ v p = v ++ "s " ++ p

objectItem :: State -> Int -> ItemType -> String
objectItem _ n Ring = makeObject n id "ring"
Expand Down
4 changes: 2 additions & 2 deletions src/LambdaHack.hs
Expand Up @@ -76,8 +76,8 @@ generate config session msg =
[ (Potion PotionWater, Clear),
(Potion PotionHealing, White) ]
ploc = ((\ (_,x,_) -> x) (head levels))
hp = playerHP config
player = defaultPlayer 0 ploc hp
hp = heroHP config
player = defaultHero 0 ploc hp
defState = defaultState player dng lvl
state = defState { sassocs = assocs, sconfig = config }
k = Config.getDefault 1 config "heroes" "extraHeroes"
Expand Down
14 changes: 7 additions & 7 deletions src/Level.hs
Expand Up @@ -81,7 +81,7 @@ type LMonsters = IM.IntMap Monster

data Level = Level
{ lname :: LevelName,
lplayers :: LMonsters, -- ^ all but the current heroes on the level
lheroes :: LMonsters, -- ^ all but the current selected hero on the level
lsize :: (Y,X),
lmonsters :: [Monster],
lsmell :: SMap,
Expand All @@ -98,33 +98,33 @@ updateSMap f lvl = lvl { lsmell = f (lsmell lvl) }
updateMonsters :: ([Monster] -> [Monster]) -> Level -> Level
updateMonsters f lvl = lvl { lmonsters = f (lmonsters lvl) }

updatePlayers :: (LMonsters -> LMonsters) -> Level -> Level
updatePlayers f lvl = lvl { lplayers = f (lplayers lvl) }
updateHeroes :: (LMonsters -> LMonsters) -> Level -> Level
updateHeroes f lvl = lvl { lheroes = f (lheroes lvl) }

lmEmpty :: LMonsters
lmEmpty = IM.empty

instance Binary Level where
put (Level nm pls sz@(sy,sx) ms lsmell lmap lmeta) =
put (Level nm hs sz@(sy,sx) ms lsmell lmap lmeta) =
do
put nm
put sz
put ms
put pls
put hs
put [ lsmell ! (y,x) | y <- [0..sy], x <- [0..sx] ]
put [ lmap ! (y,x) | y <- [0..sy], x <- [0..sx] ]
put lmeta
get = do
nm <- get
sz@(sy,sx) <- get
ms <- get
pls <- get
hs <- get
xs <- get
let lsmell = M.fromList (zip [ (y,x) | y <- [0..sy], x <- [0..sx] ] xs)
xs <- get
let lmap = M.fromList (zip [ (y,x) | y <- [0..sy], x <- [0..sx] ] xs)
lmeta <- get
return (Level nm pls sz ms lsmell lmap lmeta)
return (Level nm hs sz ms lsmell lmap lmeta)

type LMap = Map (Y,X) (Tile,Tile)
type SMap = Map (Y,X) Time
Expand Down
40 changes: 20 additions & 20 deletions src/Monster.hs
Expand Up @@ -14,37 +14,37 @@ import qualified Config
defaultBaseHP :: Int
defaultBaseHP = 50

-- | Hit points of the player. Experimentally balanced for multiple heroes.
playerHP :: Config.CP -> Int
playerHP config =
-- | Hit points of the hero. Experimentally balanced for multiple heroes.
heroHP :: Config.CP -> Int
heroHP config =
let b = Config.getDefault defaultBaseHP config "heroes" "baseHp"
k = Config.getDefault 0 config "heroes" "extraHeroes"
in b `div` (k + 1)

-- | Time the player can be traced by monsters. TODO: Make configurable.
-- | Time a hero can be traced by monsters. TODO: Make configurable.
smellTimeout :: Time
smellTimeout = 1000

-- | Initial player.
defaultPlayer :: Int -> Loc -> Int -> Player
defaultPlayer n ploc hp =
Monster (Player n) hp hp Nothing TNone ploc [] 'a' 10 0
-- | Initial hero.
defaultHero :: Int -> Loc -> Int -> Hero
defaultHero n ploc hp =
Monster (Hero n) hp hp Nothing TNone ploc [] 'a' 10 0

-- | The serial number of the plaer. At this number he appears
-- in level player maps. TODO: strengthen the type to avoid the error?
playerNumber :: Player -> Int
playerNumber pl = case mtype pl of
Player k -> k
_ -> error "playerNumber"
-- | The serial number of the hero. At this number he appears
-- in level hero intmaps. TODO: strengthen the type to avoid the error?
heroNumber :: Hero -> Int
heroNumber pl = case mtype pl of
Hero k -> k
_ -> error "heroNumber"

type Player = Monster
type Hero = Monster

data Monster = Monster
{ mtype :: !MonsterType,
mhpmax :: !Int,
mhp :: !Int,
mdir :: Maybe Dir, -- for monsters: the dir the monster last moved;
-- for the player: the dir the player is running
-- for heroes: the dir the hero is running
mtarget :: Target,
mloc :: !Loc,
mitems :: [Item], -- inventory
Expand Down Expand Up @@ -80,21 +80,21 @@ instance Binary Monster where
return (Monster mt mhpm mhp md tgt ml minv mletter mspeed mtime)

data MonsterType =
Player Int
Hero Int
| Eye
| FastEye
| Nose
deriving (Show, Eq)

instance Binary MonsterType where
put (Player n) = putWord8 0 >> put n
put (Hero n) = putWord8 0 >> put n
put Eye = putWord8 1
put FastEye = putWord8 2
put Nose = putWord8 3
get = do
tag <- getWord8
case tag of
0 -> liftM Player get
0 -> liftM Hero get
1 -> return Eye
2 -> return FastEye
3 -> return Nose
Expand Down Expand Up @@ -173,7 +173,7 @@ insertMonster = insertMonster' 0
in (n', m' : ms')

viewMonster :: MonsterType -> (Char, Attr -> Attr)
viewMonster (Player n) = (if n < 1 || n > 9 then '@' else head (show n),
viewMonster (Hero n) = (if n < 1 || n > 9 then '@' else head (show n),
setBG white . setFG black)
viewMonster Eye = ('e', setFG red)
viewMonster FastEye = ('e', setFG blue)
Expand Down
18 changes: 9 additions & 9 deletions src/State.hs
Expand Up @@ -17,7 +17,7 @@ import Message
-- In practice, we maintain extra state, but that state is state
-- accumulated during a turn or relevant only to the current session.
data State = State
{ splayer :: Player, -- ^ the selected hero
{ splayer :: Hero, -- ^ the selected hero
slook :: Maybe Look, -- ^ cursor, new target, initial level
shistory :: [Message],
ssensory :: SensoryMode,
Expand All @@ -38,7 +38,7 @@ data Look = Look
}
deriving Show

defaultState :: Player -> Dungeon -> Level -> State
defaultState :: Hero -> Dungeon -> Level -> State
defaultState player dng lvl =
State
player
Expand All @@ -52,18 +52,18 @@ defaultState player dng lvl =
lvl
(Config.CP Config.empty_CP)

updatePlayer :: (Monster -> Monster) -> State -> State
updatePlayer :: (Hero -> Hero) -> State -> State
updatePlayer f s = s { splayer = f (splayer s) }

levelHeroList :: State -> [Player]
levelHeroList :: State -> [Hero]
levelHeroList (State { splayer = player,
slevel = Level { lplayers = pls } }) =
player : IM.elems pls
slevel = Level { lheroes = hs } }) =
player : IM.elems hs

levelHeroAssocs :: State -> [(Int, Player)]
levelHeroAssocs :: State -> [(Int, Hero)]
levelHeroAssocs (State { splayer = player,
slevel = Level { lplayers = pls } }) =
(playerNumber player, player) : IM.assocs pls
slevel = Level { lheroes = hs } }) =
(heroNumber player, player) : IM.assocs hs

updateLook :: (Maybe Look -> Maybe Look) -> State -> State
updateLook f s = s { slook = f (slook s) }
Expand Down
6 changes: 4 additions & 2 deletions src/StrategyState.hs
Expand Up @@ -29,8 +29,10 @@ strategy m@(Monster { mtype = mt, mloc = me, mdir = mdir })
-- TODO: set monster targets and then prefer targets to other heroes
plocs = L.map mloc (levelHeroList state)
plds = L.map (\ l -> (distance (me, l), l)) plocs
-- we have to sort the list to avoid bias towards the currently selected
-- hero; instead monsters will prefer heroes with smaller locations
-- Here "player" is the hero chased by the monster. As soon as the monster
-- hits, this hero will really become 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.
(pdist, ploc) = L.head (L.sort plds)
-- TODO: currently even invisible heroes are targeted if _any_ hero
-- is visible; each hero should carry his own perception to check
Expand Down

0 comments on commit 081101a

Please sign in to comment.