{-# LANGUAGE DeriveGeneric #-}
module Game.LambdaHack.Client.State
( StateClient(..), AlterLid, BfsAndPath(..), TgtAndPath(..)
, emptyStateClient, cycleMarkSuspect
, updateTarget, getTarget, updateLeader, sside, sleader
) where
import Prelude ()
import Game.LambdaHack.Common.Prelude
import Data.Binary
import qualified Data.EnumMap.Lazy as LEM
import qualified Data.EnumMap.Strict as EM
import qualified Data.EnumSet as ES
import qualified Data.Map.Strict as M
import GHC.Generics (Generic)
import qualified System.Random as R
import Game.LambdaHack.Atomic
import Game.LambdaHack.Client.Bfs
import Game.LambdaHack.Client.ClientOptions
import Game.LambdaHack.Common.Actor
import Game.LambdaHack.Common.ActorState
import Game.LambdaHack.Common.Faction
import Game.LambdaHack.Common.Item
import Game.LambdaHack.Common.Kind
import Game.LambdaHack.Common.Level
import Game.LambdaHack.Common.Perception
import Game.LambdaHack.Common.Point
import qualified Game.LambdaHack.Common.PointArray as PointArray
import Game.LambdaHack.Common.State
import Game.LambdaHack.Content.ModeKind (ModeKind)
data StateClient = StateClient
{ seps :: Int
, stargetD :: EM.EnumMap ActorId TgtAndPath
, sfleeD :: EM.EnumMap ActorId Point
, sexplored :: ES.EnumSet LevelId
, sbfsD :: EM.EnumMap ActorId BfsAndPath
, sundo :: [CmdAtomic]
, sdiscoBenefit :: DiscoveryBenefit
, sfper :: PerLid
, salter :: AlterLid
, srandom :: R.StdGen
, _sleader :: Maybe ActorId
, _sside :: FactionId
, squit :: Bool
, scurChal :: Challenge
, snxtChal :: Challenge
, snxtScenario :: Int
, smarkSuspect :: Int
, scondInMelee :: LEM.EnumMap LevelId Bool
, svictories :: EM.EnumMap (ContentId ModeKind) (M.Map Challenge Int)
, soptions :: ClientOptions
}
deriving Show
type AlterLid = EM.EnumMap LevelId (PointArray.Array Word8)
data BfsAndPath =
BfsInvalid
| BfsAndPath { bfsArr :: PointArray.Array BfsDistance
, bfsPath :: EM.EnumMap Point AndPath
}
deriving Show
data TgtAndPath = TgtAndPath {tapTgt :: Target, tapPath :: AndPath}
deriving (Show, Generic)
instance Binary TgtAndPath
emptyStateClient :: FactionId -> StateClient
emptyStateClient _sside =
StateClient
{ seps = fromEnum _sside
, stargetD = EM.empty
, sfleeD = EM.empty
, sexplored = ES.empty
, sbfsD = EM.empty
, sundo = []
, sdiscoBenefit = EM.empty
, sfper = EM.empty
, salter = EM.empty
, srandom = R.mkStdGen 42
, _sleader = Nothing
, _sside
, squit = False
, scurChal = defaultChallenge
, snxtChal = defaultChallenge
, snxtScenario = 0
, smarkSuspect = 1
, scondInMelee = LEM.empty
, svictories = EM.empty
, soptions = defClientOptions
}
cycleMarkSuspect :: StateClient -> StateClient
cycleMarkSuspect s@StateClient{smarkSuspect} =
s {smarkSuspect = (smarkSuspect + 1) `mod` 3}
updateTarget :: ActorId -> (Maybe Target -> Maybe Target) -> StateClient
-> StateClient
updateTarget aid f cli =
let f2 tp = case f $ fmap tapTgt tp of
Nothing -> Nothing
Just tgt -> Just $ TgtAndPath tgt NoPath
in cli {stargetD = EM.alter f2 aid (stargetD cli)}
getTarget :: ActorId -> StateClient -> Maybe Target
getTarget aid cli = fmap tapTgt $ EM.lookup aid $ stargetD cli
updateLeader :: ActorId -> State -> StateClient -> StateClient
updateLeader leader s cli =
let side1 = bfid $ getActorBody leader s
side2 = sside cli
in assert (side1 == side2 `blame` "enemy actor becomes our leader"
`swith` (side1, side2, leader, s))
$ cli {_sleader = Just leader}
sside :: StateClient -> FactionId
sside = _sside
sleader :: StateClient -> Maybe ActorId
sleader = _sleader
instance Binary StateClient where
put StateClient{..} = do
put seps
put stargetD
put sfleeD
put sexplored
put sundo
put sdiscoBenefit
put (show srandom)
put _sleader
put _sside
put scurChal
put snxtChal
put snxtScenario
put smarkSuspect
put scondInMelee
put svictories
#ifdef WITH_EXPENSIVE_ASSERTIONS
put sfper
#endif
get = do
seps <- get
stargetD <- get
sfleeD <- get
sexplored <- get
sundo <- get
sdiscoBenefit <- get
g <- get
_sleader <- get
_sside <- get
scurChal <- get
snxtChal <- get
snxtScenario <- get
smarkSuspect <- get
scondInMelee <- get
svictories <- get
let sbfsD = EM.empty
salter = EM.empty
srandom = read g
squit = False
soptions = defClientOptions
#ifndef WITH_EXPENSIVE_ASSERTIONS
sfper = EM.empty
#else
sfper <- get
#endif
return $! StateClient{..}