Safe Haskell | None |
---|---|
Language | Haskell2010 |
Game.LambdaHack.Client.UI.SessionUI
Description
The client UI session state.
Synopsis
- 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
- type ItemDictUI = EnumMap ItemId LevelId
- newtype ItemRoles = ItemRoles (EnumMap SLore (EnumSet ItemId))
- data AimMode = AimMode {}
- newtype KeyMacro = KeyMacro {
- unKeyMacro :: [KM]
- data KeyMacroFrame = KeyMacroFrame {
- keyMacroBuffer :: Either [KM] KeyMacro
- keyPending :: KeyMacro
- keyLast :: Maybe KM
- data RunParams = RunParams {
- runLeader :: ActorId
- runMembers :: [ActorId]
- runInitial :: Bool
- runStopMsg :: Maybe Text
- runWaiting :: Int
- data ChosenLore
- = ChosenLore [(ActorId, Actor)] [(ItemId, ItemQuant)]
- | ChosenNothing
- emptySessionUI :: UIOptions -> SessionUI
- emptyMacroFrame :: KeyMacroFrame
- cycleMarkVision :: Int -> SessionUI -> SessionUI
- toggleMarkSmell :: SessionUI -> SessionUI
- cycleOverrideTut :: Int -> SessionUI -> SessionUI
- getActorUI :: ActorId -> SessionUI -> ActorUI
Documentation
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 |
A collection of item identifier sets indicating what roles (possibly many) an item has assigned.
Current aiming mode of a client.
Constructors
AimMode | |
Fields |
Instances
Eq AimMode Source # | |
Show AimMode Source # | |
Generic AimMode Source # | |
Binary AimMode Source # | |
type Rep AimMode Source # | |
Defined in Game.LambdaHack.Client.UI.SessionUI type Rep AimMode = D1 ('MetaData "AimMode" "Game.LambdaHack.Client.UI.SessionUI" "LambdaHack-0.11.0.0-inplace" 'False) (C1 ('MetaCons "AimMode" 'PrefixI 'True) (S1 ('MetaSel ('Just "aimLevelId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 LevelId) :*: S1 ('MetaSel ('Just "detailLevel") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 DetailLevel))) |
In-game macros. We record menu navigation keystrokes and keystrokes
bound to commands with one exception --- we exclude keys that invoke
the Record
command, to avoid surprises.
Keys are kept in the same order in which they're meant to be replayed,
i.e. the first element of the list is replayed also as the first one.
Constructors
KeyMacro | |
Fields
|
data KeyMacroFrame Source #
Local macro buffer frame. Predefined macros have their own in-game macro
buffer, allowing them to record in-game macro, queue actions and repeat
the last macro's action.
Running predefined macro pushes new KeyMacroFrame
onto the stack. We pop
buffers from the stack if locally there are no actions pending to be handled.
Constructors
KeyMacroFrame | |
Fields
|
Instances
Show KeyMacroFrame Source # | |
Defined in Game.LambdaHack.Client.UI.SessionUI Methods showsPrec :: Int -> KeyMacroFrame -> ShowS # show :: KeyMacroFrame -> String # showList :: [KeyMacroFrame] -> ShowS # |
Parameters of the current run.
Constructors
RunParams | |
Fields
|
data ChosenLore Source #
Last lore being aimed at.
Constructors
ChosenLore [(ActorId, Actor)] [(ItemId, ItemQuant)] | |
ChosenNothing |
emptySessionUI :: UIOptions -> SessionUI Source #
toggleMarkSmell :: SessionUI -> SessionUI Source #