{-# LANGUAGE DeriveGeneric #-}
module Game.LambdaHack.Common.Actor
(
ActorId
, Actor(..), ResDelta(..), ActorAspect
, deltaSerious, deltaMild, actorCanMelee
, momentarySpeed, gearSpeed, braced, actorTemplate, waitedLastTurn, actorDying
, hpTooLow, calmEnough, hpEnough
, checkAdjacent, eqpOverfull, eqpFreeN
, ActorDict, monsterGenChance, smellTimeout
) where
import Prelude ()
import Game.LambdaHack.Common.Prelude
import Data.Binary
import qualified Data.EnumMap.Strict as EM
import Data.Int (Int64)
import Data.Ratio
import GHC.Generics (Generic)
import qualified Game.LambdaHack.Common.Ability as Ability
import qualified Game.LambdaHack.Common.Dice as Dice
import Game.LambdaHack.Common.Item
import qualified Game.LambdaHack.Common.ItemAspect as IA
import Game.LambdaHack.Common.Misc
import Game.LambdaHack.Common.Point
import Game.LambdaHack.Common.Random
import Game.LambdaHack.Common.Time
import Game.LambdaHack.Common.Vector
data Actor = Actor
{
btrunk :: ItemId
, bhp :: Int64
, bhpDelta :: ResDelta
, bcalm :: Int64
, bcalmDelta :: ResDelta
, bpos :: Point
, boldpos :: Maybe Point
, blid :: LevelId
, bfid :: FactionId
, btrajectory :: Maybe ([Vector], Speed)
, borgan :: ItemBag
, beqp :: ItemBag
, binv :: ItemBag
, bweapon :: Int
, bwait :: Bool
, bproj :: Bool
}
deriving (Show, Eq, Generic)
instance Binary Actor
data ResDelta = ResDelta
{ resCurrentTurn :: (Int64, Int64)
, resPreviousTurn :: (Int64, Int64)
}
deriving (Show, Eq, Generic)
instance Binary ResDelta
type ActorAspect = EM.EnumMap ActorId IA.AspectRecord
type ActorDict = EM.EnumMap ActorId Actor
deltaSerious :: ResDelta -> Bool
deltaSerious ResDelta{..} =
fst resCurrentTurn < 0 && fst resCurrentTurn /= minusM
|| fst resPreviousTurn < 0 && fst resPreviousTurn /= minusM
deltaMild :: ResDelta -> Bool
deltaMild ResDelta{..} = fst resCurrentTurn == minusM
|| fst resPreviousTurn == minusM
actorCanMelee :: ActorAspect -> ActorId -> Actor -> Bool
actorCanMelee actorAspect aid b =
let ar = actorAspect EM.! aid
actorMaxSk = IA.aSkills ar
condUsableWeapon = bweapon b >= 0
canMelee = EM.findWithDefault 0 Ability.AbMelee actorMaxSk > 0
in condUsableWeapon && canMelee
momentarySpeed :: Actor -> IA.AspectRecord -> Speed
momentarySpeed !b ar =
case btrajectory b of
Nothing -> gearSpeed ar
Just (_, speed) -> speed
gearSpeed :: IA.AspectRecord -> Speed
gearSpeed IA.AspectRecord{aSpeed} =
toSpeed $ max minSpeed aSpeed
braced :: Actor -> Bool
braced = bwait
actorTemplate :: ItemId -> Int64 -> Int64 -> Point -> LevelId -> FactionId
-> Bool
-> Actor
actorTemplate btrunk bhp bcalm bpos blid bfid bproj =
let btrajectory = Nothing
boldpos = Nothing
borgan = EM.empty
beqp = EM.empty
binv = EM.empty
bweapon = 0
bwait = False
bhpDelta = ResDelta (0, 0) (0, 0)
bcalmDelta = ResDelta (0, 0) (0, 0)
in Actor{..}
waitedLastTurn :: Actor -> Bool
{-# INLINE waitedLastTurn #-}
waitedLastTurn = bwait
actorDying :: Actor -> Bool
actorDying b = bhp b <= 0
|| bproj b && maybe True (null . fst) (btrajectory b)
hpTooLow :: Actor -> IA.AspectRecord -> Bool
hpTooLow b IA.AspectRecord{aMaxHP} =
5 * bhp b < xM aMaxHP && bhp b <= xM 40 || bhp b <= oneM
calmEnough :: Actor -> IA.AspectRecord -> Bool
calmEnough b IA.AspectRecord{aMaxCalm} =
let calmMax = max 1 aMaxCalm
in 2 * xM calmMax <= 3 * bcalm b && bcalm b > xM 10
hpEnough :: Actor -> IA.AspectRecord -> Bool
hpEnough b IA.AspectRecord{aMaxHP} =
xM aMaxHP <= 2 * bhp b && bhp b > oneM
checkAdjacent :: Actor -> Actor -> Bool
checkAdjacent sb tb = blid sb == blid tb && adjacent (bpos sb) (bpos tb)
eqpOverfull :: Actor -> Int -> Bool
eqpOverfull b n = let size = sum $ map fst $ EM.elems $ beqp b
in assert (size <= 10 `blame` (b, n, size))
$ size + n > 10
eqpFreeN :: Actor -> Int
eqpFreeN b = let size = sum $ map fst $ EM.elems $ beqp b
in assert (size <= 10 `blame` (b, size))
$ 10 - size
monsterGenChance :: Dice.AbsDepth -> Dice.AbsDepth -> Int -> Int -> Rnd Bool
monsterGenChance (Dice.AbsDepth n) (Dice.AbsDepth totalDepth)
lvlAlreadySpawned actorCoeff =
assert (totalDepth > 0 && n > 0) $
let scaledDepth = n * 10 `div` totalDepth
coeff = actorCoeff * (lvlAlreadySpawned - scaledDepth - 2)
in chance $ 1%fromIntegral (coeff `max` 1)
smellTimeout :: Delta Time
smellTimeout = timeDeltaScale (Delta timeTurn) 100