module Game.LambdaHack.Server.State
( StateServer(..), ActorTime
, emptyStateServer, updateActorTime, ageActor
) where
import Prelude ()
import Game.LambdaHack.Common.Prelude
import Data.Binary
import qualified Data.EnumMap.Strict as EM
import qualified Data.EnumSet as ES
import qualified Data.HashMap.Strict as HM
import qualified System.Random as R
import Game.LambdaHack.Atomic
import Game.LambdaHack.Common.Actor
import Game.LambdaHack.Common.Faction
import Game.LambdaHack.Common.Item
import Game.LambdaHack.Common.Level
import Game.LambdaHack.Common.Perception
import Game.LambdaHack.Common.State
import Game.LambdaHack.Common.Time
import Game.LambdaHack.Server.Fov
import Game.LambdaHack.Server.ItemRev
import Game.LambdaHack.Server.ServerOptions
data StateServer = StateServer
{ sactorTime :: ActorTime
, sactorStasis :: ES.EnumSet ActorId
, sdiscoKindRev :: DiscoveryKindRev
, suniqueSet :: UniqueSet
, sitemSeedD :: ItemSeedDict
, sitemRev :: ItemRev
, sflavour :: FlavourMap
, sacounter :: ActorId
, sicounter :: ItemId
, snumSpawned :: EM.EnumMap LevelId Int
, sundo :: [CmdAtomic]
, sclientStates :: EM.EnumMap FactionId State
, sperFid :: PerFid
, sperValidFid :: PerValidFid
, sperCacheFid :: PerCacheFid
, sfovLucidLid :: FovLucidLid
, sfovClearLid :: FovClearLid
, sfovLitLid :: FovLitLid
, sarenas :: [LevelId]
, svalidArenas :: Bool
, srandom :: R.StdGen
, srngs :: RNGs
, sbreakLoop :: Bool
, sbreakASAP :: Bool
, swriteSave :: Bool
, soptions :: ServerOptions
, soptionsNxt :: ServerOptions
}
deriving Show
type ActorTime =
EM.EnumMap FactionId (EM.EnumMap LevelId (EM.EnumMap ActorId Time))
emptyStateServer :: StateServer
emptyStateServer =
StateServer
{ sactorTime = EM.empty
, sactorStasis = ES.empty
, sdiscoKindRev = emptyDiscoveryKindRev
, suniqueSet = ES.empty
, sitemSeedD = EM.empty
, sitemRev = HM.empty
, sflavour = emptyFlavourMap
, sacounter = toEnum 0
, sicounter = toEnum 0
, snumSpawned = EM.empty
, sundo = []
, sclientStates = EM.empty
, sperFid = EM.empty
, sperValidFid = EM.empty
, sperCacheFid = EM.empty
, sfovLucidLid = EM.empty
, sfovClearLid = EM.empty
, sfovLitLid = EM.empty
, sarenas = []
, svalidArenas = False
, srandom = R.mkStdGen 42
, srngs = RNGs { dungeonRandomGenerator = Nothing
, startingRandomGenerator = Nothing }
, sbreakLoop = False
, sbreakASAP = False
, swriteSave = False
, soptions = defServerOptions
, soptionsNxt = defServerOptions
}
updateActorTime :: FactionId -> LevelId -> ActorId -> Time -> ActorTime
-> ActorTime
updateActorTime !fid !lid !aid !time =
EM.adjust (EM.adjust (EM.insert aid time) lid) fid
ageActor :: FactionId -> LevelId -> ActorId -> Delta Time -> ActorTime
-> ActorTime
ageActor !fid !lid !aid !delta =
EM.adjust (EM.adjust (EM.adjust (`timeShift` delta) aid) lid) fid
instance Binary StateServer where
put StateServer{..} = do
put sactorTime
put sactorStasis
put sdiscoKindRev
put suniqueSet
put sitemSeedD
put sitemRev
put sflavour
put sacounter
put sicounter
put snumSpawned
put sclientStates
put (show srandom)
put srngs
put soptions
get = do
sactorTime <- get
sactorStasis <- get
sdiscoKindRev <- get
suniqueSet <- get
sitemSeedD <- get
sitemRev <- get
sflavour <- get
sacounter <- get
sicounter <- get
snumSpawned <- get
sclientStates <- get
g <- get
srngs <- get
soptions <- get
let srandom = read g
sundo = []
sperFid = EM.empty
sperValidFid = EM.empty
sperCacheFid = EM.empty
sfovLucidLid = EM.empty
sfovClearLid = EM.empty
sfovLitLid = EM.empty
sarenas = []
svalidArenas = False
sbreakLoop = False
sbreakASAP = False
swriteSave = False
soptionsNxt = defServerOptions
return $! StateServer{..}