Safe Haskell | None |
---|---|
Language | Haskell2010 |
Game.LambdaHack.Client.UI
Description
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.
This module is leaking quite a bit of implementation details for the sake of Game.LambdaHack.Client.LoopM. After multiplayer is enabled again and the new requirements sorted out, this should be redesigned and some code moved down the module hierarhy tree, exposing a smaller API here.
Synopsis
- queryUI :: (MonadClient m, MonadClientUI m) => m (Maybe RequestUI)
- queryUIunderAI :: (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)
- putSession :: MonadClientUI m => SessionUI -> m ()
- anyKeyPressed :: MonadClientUI m => m Bool
- resetPressedKeys :: MonadClientUI m => m ()
- data SessionUI = SessionUI {
- sreqPending :: Maybe RequestUI
- sreqDelay :: ReqDelay
- sreqQueried :: Bool
- sregainControl :: Bool
- sxhair :: Maybe Target
- sxhairGoTo :: Maybe Target
- sactorUI :: ActorDictUI
- sitemUI :: ItemDictUI
- sroles :: ItemRoles
- 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
- svictories :: EnumMap (ContentId ModeKind) (Map Challenge Int)
- scampings :: EnumSet (ContentId ModeKind)
- srestarts :: EnumSet (ContentId ModeKind)
- spointer :: PointUI
- sautoYes :: Bool
- smacroFrame :: KeyMacroFrame
- smacroStack :: [KeyMacroFrame]
- slastLost :: EnumSet ActorId
- swaitTimes :: Int
- swasAutomated :: Bool
- smarkVision :: Int
- smarkSmell :: Bool
- snxtScenario :: Int
- scurTutorial :: Bool
- snxtTutorial :: Bool
- soverrideTut :: Maybe Bool
- susedHints :: Set Msg
- smuteMessages :: Bool
- smenuIxMap :: Map String Int
- schosenLore :: ChosenLore
- sdisplayNeeded :: Bool
- sturnDisplayed :: Bool
- sreportNull :: Bool
- sstart :: POSIXTime
- sgstart :: POSIXTime
- sallTime :: Time
- snframes :: Int
- sallNframes :: Int
- srandomUI :: SMGen
- data ReqDelay
- emptySessionUI :: UIOptions -> SessionUI
- watchRespUpdAtomicUI :: MonadClientUI m => UpdAtomic -> m ()
- watchRespSfxAtomicUI :: MonadClientUI m => SfxAtomic -> m ()
- data CCUI = CCUI {}
- data UIOptions
- applyUIOptions :: COps -> UIOptions -> ClientOptions -> ClientOptions
- uOverrideCmdline :: UIOptions -> [String]
- mkUIOptions :: RuleContent -> ClientOptions -> IO UIOptions
- data ChanFrontend
- chanFrontend :: MonadClientUI m => ScreenContent -> ClientOptions -> m ChanFrontend
- tryRestore :: MonadClientUI m => m (Maybe (StateClient, Maybe SessionUI))
- clientPrintUI :: MonadClientUI m => Text -> m ()
- pushReportFrame :: MonadClientUI m => m ()
- msgAdd :: (MonadClientUI m, MsgShared a) => a -> Text -> m ()
- data MsgClassShow
- stepQueryUIwithLeader :: (MonadClient m, MonadClientUI m) => m (Maybe RequestUI)
- stepQueryUI :: (MonadClient m, MonadClientUI m) => m (Maybe ReqUI)
Querying the human player
queryUI :: (MonadClient m, MonadClientUI m) => m (Maybe RequestUI) Source #
Handle the move of a human player.
queryUIunderAI :: (MonadClient m, MonadClientUI m) => m RequestUI Source #
UI monad operations
class MonadClientRead m => MonadClientUI m where Source #
The monad that gives the client access to UI operations, but not to modifying client state, except for the client-side pointman (as opposed to pointman stores in faction data in main game state), which is more of a UI concept, but is shared with AI to be able to keep it when switching AI on/off and to save on typing.
Methods
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 Methods 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 # |
putSession :: MonadClientUI m => SessionUI -> m () Source #
anyKeyPressed :: MonadClientUI m => m Bool Source #
resetPressedKeys :: MonadClientUI m => m () Source #
UI session type
The information that is used across a human player playing session, including many consecutive games in a single session, including playing different teams. Some of it is saved, some is reset when a new playing session starts. Nothing is tied to a faction/team, but instead all to UI configuration and UI input and display history. An important component is the frontend session.
Constructors
SessionUI | |
Fields
|
Constructors
ReqDelayNot | |
ReqDelayHandled | |
ReqDelayAlarm |
emptySessionUI :: UIOptions -> SessionUI Source #
Updating UI state wrt game state changes
watchRespUpdAtomicUI :: 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. Doesn't modify client state (except a few fields), but only client session (e.g., by displaying messages). This is enforced by types.
watchRespSfxAtomicUI :: 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 UI content types, gathered together.
Constructors
CCUI | |
Fields |
Options that affect the UI of the client, specified in the config file. More documentation is in the default config file.
Instances
applyUIOptions :: COps -> UIOptions -> ClientOptions -> ClientOptions Source #
Modify client options with UI options.
uOverrideCmdline :: UIOptions -> [String] Source #
mkUIOptions :: RuleContent -> ClientOptions -> IO UIOptions Source #
Read and parse UI config file.
Assorted operations and types
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.
tryRestore :: MonadClientUI m => m (Maybe (StateClient, Maybe SessionUI)) Source #
Try to read saved client game state from the file system.
clientPrintUI :: MonadClientUI m => Text -> m () Source #
pushReportFrame :: MonadClientUI m => m () Source #
msgAdd :: (MonadClientUI m, MsgShared a) => a -> Text -> m () Source #
Add a message to the current report.
data MsgClassShow Source #
Constructors
MsgPromptGeneric | |
MsgPromptFocus | |
MsgPromptMention | |
MsgPromptModify | |
MsgPromptActors | |
MsgPromptItems | |
MsgPromptAction | |
MsgActionAlert | |
MsgSpottedThreat |
Instances
Internal operations
stepQueryUIwithLeader :: (MonadClient m, MonadClientUI m) => m (Maybe RequestUI) Source #
stepQueryUI :: (MonadClient m, MonadClientUI m) => m (Maybe ReqUI) Source #
Let the human player issue commands until any command takes time.