Safe Haskell | None |
---|---|
Language | Haskell2010 |
Ways for the client to use player input via UI to produce server requests, based on the client's view (visualized for the player) of the game state.
Synopsis
- queryUI :: (MonadClient m, MonadClientUI m) => m RequestUI
- class MonadClientRead m => MonadClientUI m where
- getsSession :: (SessionUI -> a) -> m a
- modifySession :: (SessionUI -> SessionUI) -> m ()
- updateClientLeader :: ActorId -> m ()
- getCacheBfs :: ActorId -> m (Array BfsDistance)
- getCachePath :: ActorId -> Point -> m (Maybe AndPath)
- data SessionUI = SessionUI {
- sxhair :: Maybe Target
- sactorUI :: ActorDictUI
- sitemUI :: ItemDictUI
- sslots :: ItemSlots
- slastItemMove :: Maybe (CStore, CStore)
- schanF :: ChanFrontend
- sccui :: CCUI
- sUIOptions :: UIOptions
- saimMode :: Maybe AimMode
- sxhairMoused :: Bool
- sitemSel :: Maybe (ItemId, CStore, Bool)
- sselected :: EnumSet ActorId
- srunning :: Maybe RunParams
- shistory :: History
- spointer :: Point
- slastRecord :: LastRecord
- slastPlay :: [KM]
- slastLost :: EnumSet ActorId
- swaitTimes :: Int
- smarkVision :: Bool
- smarkSmell :: Bool
- smenuIxMap :: Map String Int
- sdisplayNeeded :: Bool
- shintMode :: HintMode
- sreportNull :: Bool
- sstart :: POSIXTime
- sgstart :: POSIXTime
- sallTime :: Time
- snframes :: Int
- sallNframes :: Int
- displayRespUpdAtomicUI :: MonadClientUI m => UpdAtomic -> m ()
- displayRespSfxAtomicUI :: MonadClientUI m => SfxAtomic -> m ()
- data CCUI = CCUI {}
- data UIOptions
- applyUIOptions :: COps -> UIOptions -> ClientOptions -> ClientOptions
- uCmdline :: UIOptions -> [String]
- mkUIOptions :: COps -> Bool -> IO UIOptions
- data ChanFrontend
- chanFrontend :: MonadClientUI m => ScreenContent -> ClientOptions -> m ChanFrontend
- promptAdd :: MonadClientUI m => Text -> m ()
- tryRestore :: MonadClientUI m => m (Maybe (StateClient, Maybe SessionUI))
- humanCommand :: forall m. (MonadClient m, MonadClientUI m) => m ReqUI
Querying the human player
queryUI :: (MonadClient m, MonadClientUI m) => m RequestUI Source #
Handle the move of a human player.
UI monad and session type
class MonadClientRead m => MonadClientUI m where Source #
The monad that gives the client access to UI operations, but not to modifying client state.
getsSession :: (SessionUI -> a) -> m a Source #
modifySession :: (SessionUI -> SessionUI) -> m () Source #
updateClientLeader :: ActorId -> m () Source #
getCacheBfs :: ActorId -> m (Array BfsDistance) Source #
getCachePath :: ActorId -> Point -> m (Maybe AndPath) Source #
Instances
MonadClientUI CliImplementation Source # | |
Defined in Implementation.MonadClientImplementation getsSession :: (SessionUI -> a) -> CliImplementation a Source # modifySession :: (SessionUI -> SessionUI) -> CliImplementation () Source # updateClientLeader :: ActorId -> CliImplementation () Source # getCacheBfs :: ActorId -> CliImplementation (Array BfsDistance) Source # getCachePath :: ActorId -> Point -> CliImplementation (Maybe AndPath) Source # |
The information that is used across a client playing session, including many consecutive games in a single session. Some of it is saved, some is reset when a new playing session starts. An important component is the frontend session.
SessionUI | |
|
Updating UI state wrt game state changes
displayRespUpdAtomicUI :: MonadClientUI m => UpdAtomic -> m () Source #
Visualize atomic updates sent to the client. This is done in the global state after the command is executed and after the client state is modified by the command. Don't modify client state (except a few fields), but only client session (e.g., by displaying messages). This is enforced by types.
displayRespSfxAtomicUI :: MonadClientUI m => SfxAtomic -> m () Source #
Display special effects (text, animation) sent to the client. Don't modify client state (except a few fields), but only client session (e.g., by displaying messages). This is enforced by types.
Startup and initialization
Operations for all content types, gathered together.
Options that affect the UI of the client.
Instances
applyUIOptions :: COps -> UIOptions -> ClientOptions -> ClientOptions Source #
Modify client options with UI options.
Operations exposed for Game.LambdaHack.Client.LoopM
data ChanFrontend Source #
Connection channel between a frontend and a client. Frontend acts as a server, serving keys, etc., when given frames to display.
chanFrontend :: MonadClientUI m => ScreenContent -> ClientOptions -> m ChanFrontend Source #
Initialize the frontend chosen by the player via client options.
promptAdd :: MonadClientUI m => Text -> m () Source #
Add a prompt to the current report. Do not report if it was a duplicate.
tryRestore :: MonadClientUI m => m (Maybe (StateClient, Maybe SessionUI)) Source #
Try to read saved client game state from the file system.
Internal operations
humanCommand :: forall m. (MonadClient m, MonadClientUI m) => m ReqUI Source #
Let the human player issue commands until any command takes time.