Safe Haskell | None |
---|---|
Language | Haskell2010 |
Basic server monads and related operations.
Synopsis
- class MonadStateRead m => MonadServer m where
- getsServer :: (StateServer -> a) -> m a
- modifyServer :: (StateServer -> StateServer) -> m ()
- chanSaveServer :: m (ChanSave (State, StateServer))
- liftIO :: IO a -> m a
- class MonadServer m => MonadServerAtomic m where
- execUpdAtomic :: UpdAtomic -> m ()
- execUpdAtomicSer :: UpdAtomic -> m Bool
- execUpdAtomicFid :: FactionId -> UpdAtomic -> m ()
- execUpdAtomicFidCatch :: FactionId -> UpdAtomic -> m Bool
- execSfxAtomic :: SfxAtomic -> m ()
- execSendPer :: FactionId -> LevelId -> Perception -> Perception -> Perception -> m ()
- getServer :: MonadServer m => m StateServer
- putServer :: MonadServer m => StateServer -> m ()
- debugPossiblyPrint :: MonadServer m => Text -> m ()
- debugPossiblyPrintAndExit :: MonadServer m => Text -> m ()
- serverPrint :: MonadServer m => Text -> m ()
- saveServer :: MonadServer m => m ()
- dumpRngs :: MonadServer m => RNGs -> m ()
- restoreScore :: forall m. MonadServer m => COps -> m ScoreDict
- registerScore :: MonadServer m => Status -> FactionId -> m ()
- rndToAction :: MonadServer m => Rnd a -> m a
- getSetGen :: MonadServer m => Maybe StdGen -> m StdGen
The server monad
class MonadStateRead m => MonadServer m where Source #
getsServer :: (StateServer -> a) -> m a Source #
modifyServer :: (StateServer -> StateServer) -> m () Source #
chanSaveServer :: m (ChanSave (State, StateServer)) Source #
Instances
MonadServer SerImplementation Source # | |
Defined in Implementation.MonadServerImplementation getsServer :: (StateServer -> a) -> SerImplementation a Source # modifyServer :: (StateServer -> StateServer) -> SerImplementation () Source # chanSaveServer :: SerImplementation (ChanSave (State, StateServer)) Source # liftIO :: IO a -> SerImplementation a Source # |
class MonadServer m => MonadServerAtomic m where Source #
The monad for executing atomic game state transformations.
execUpdAtomic :: UpdAtomic -> m () Source #
Execute an atomic command that changes the state on the server and on all clients that can notice it.
execUpdAtomicSer :: UpdAtomic -> m Bool Source #
Execute an atomic command that changes the state on the server only.
execUpdAtomicFid :: FactionId -> UpdAtomic -> m () Source #
Execute an atomic command that changes the state on the given single client only.
execUpdAtomicFidCatch :: FactionId -> UpdAtomic -> m Bool Source #
Execute an atomic command that changes the state
on the given single client only.
Catch AtomicFail
and indicate if it was in fact raised.
execSfxAtomic :: SfxAtomic -> m () Source #
Execute an atomic command that only displays special effects.
execSendPer :: FactionId -> LevelId -> Perception -> Perception -> Perception -> m () Source #
Instances
MonadServerAtomic SerImplementation Source # | |
Defined in Implementation.MonadServerImplementation execUpdAtomic :: UpdAtomic -> SerImplementation () Source # execUpdAtomicSer :: UpdAtomic -> SerImplementation Bool Source # execUpdAtomicFid :: FactionId -> UpdAtomic -> SerImplementation () Source # execUpdAtomicFidCatch :: FactionId -> UpdAtomic -> SerImplementation Bool Source # execSfxAtomic :: SfxAtomic -> SerImplementation () Source # execSendPer :: FactionId -> LevelId -> Perception -> Perception -> Perception -> SerImplementation () Source # |
Assorted primitives
getServer :: MonadServer m => m StateServer Source #
putServer :: MonadServer m => StateServer -> m () Source #
debugPossiblyPrint :: MonadServer m => Text -> m () Source #
debugPossiblyPrintAndExit :: MonadServer m => Text -> m () Source #
serverPrint :: MonadServer m => Text -> m () Source #
saveServer :: MonadServer m => m () Source #
dumpRngs :: MonadServer m => RNGs -> m () Source #
Dumps to stdout the RNG states from the start of the game.
restoreScore :: forall m. MonadServer m => COps -> m ScoreDict Source #
Read the high scores dictionary. Return the empty table if no file.
registerScore :: MonadServer m => Status -> FactionId -> m () Source #
Generate a new score, register it and save.
rndToAction :: MonadServer m => Rnd a -> m a Source #
Invoke pseudo-random computation with the generator kept in the state.