Skip to content

Commit

Permalink
Group modal dialog state into a record
Browse files Browse the repository at this point in the history
  • Loading branch information
kostmo committed Sep 5, 2024
1 parent 413a714 commit 162aee8
Show file tree
Hide file tree
Showing 9 changed files with 62 additions and 46 deletions.
26 changes: 13 additions & 13 deletions src/swarm-tui/Swarm/TUI/Controller.hs
Original file line number Diff line number Diff line change
Expand Up @@ -294,14 +294,14 @@ handleMainEvent forceRedraw ev = do
Web (RunWebCode e r) -> runBaseWebCode e r
UpstreamVersion _ -> error "version event should be handled by top-level handler"
VtyEvent (V.EvResize _ _) -> invalidateCache
EscapeKey | Just m <- s ^. uiState . uiGameplay . uiModal -> closeModal m
EscapeKey | Just m <- s ^. uiState . uiGameplay . uiDialogs . uiModal -> closeModal m
-- Pass to key handler (allows users to configure bindings)
-- See Note [how Swarm event handlers work]
VtyEvent (V.EvKey k m)
| isJust (B.lookupVtyEvent k m keyHandler) -> void $ B.handleKey keyHandler k m
-- pass keys on to modal event handler if a modal is open
VtyEvent vev
| isJust (s ^. uiState . uiGameplay . uiModal) -> handleModalEvent vev
| isJust (s ^. uiState . uiGameplay . uiDialogs . uiModal) -> handleModalEvent vev
MouseDown (TerrainListItem pos) V.BLeft _ _ ->
uiState . uiGameplay . uiWorldEditor . terrainList %= BL.listMoveTo pos
MouseDown (EntityPaintListItem pos) V.BLeft _ _ ->
Expand Down Expand Up @@ -367,7 +367,7 @@ handleMainEvent forceRedraw ev = do
closeModal :: Modal -> EventM Name AppState ()
closeModal m = do
safeAutoUnpause
uiState . uiGameplay . uiModal .= Nothing
uiState . uiGameplay . uiDialogs . uiModal .= Nothing
-- message modal is not autopaused, so update notifications when leaving it
when ((m ^. modalType) == MessagesModal) $ do
t <- use $ gameState . temporal . ticks
Expand All @@ -377,7 +377,7 @@ closeModal m = do
handleModalEvent :: V.Event -> EventM Name AppState ()
handleModalEvent = \case
V.EvKey V.KEnter [] -> do
mdialog <- preuse $ uiState . uiGameplay . uiModal . _Just . modalDialog
mdialog <- preuse $ uiState . uiGameplay . uiDialogs . uiModal . _Just . modalDialog
toggleModal QuitModal
case dialogSelection =<< mdialog of
Just (Button QuitButton, _) -> quitGame
Expand All @@ -391,33 +391,33 @@ handleModalEvent = \case
startGame siPair Nothing
_ -> return ()
ev -> do
Brick.zoom (uiState . uiGameplay . uiModal . _Just . modalDialog) (handleDialogEvent ev)
modal <- preuse $ uiState . uiGameplay . uiModal . _Just . modalType
Brick.zoom (uiState . uiGameplay . uiDialogs . uiModal . _Just . modalDialog) (handleDialogEvent ev)
modal <- preuse $ uiState . uiGameplay . uiDialogs . uiModal . _Just . modalType
case modal of
Just TerrainPaletteModal ->
refreshList $ uiState . uiGameplay . uiWorldEditor . terrainList
Just EntityPaletteModal -> do
refreshList $ uiState . uiGameplay . uiWorldEditor . entityPaintList
Just GoalModal -> case ev of
V.EvKey (V.KChar '\t') [] -> uiState . uiGameplay . uiGoal . focus %= focusNext
V.EvKey (V.KChar '\t') [] -> uiState . uiGameplay . uiDialogs . uiGoal . focus %= focusNext
_ -> do
focused <- use $ uiState . uiGameplay . uiGoal . focus
focused <- use $ uiState . uiGameplay . uiDialogs . uiGoal . focus
case focusGetCurrent focused of
Just (GoalWidgets w) -> case w of
ObjectivesList -> do
lw <- use $ uiState . uiGameplay . uiGoal . listWidget
lw <- use $ uiState . uiGameplay . uiDialogs . uiGoal . listWidget
newList <- refreshGoalList lw
uiState . uiGameplay . uiGoal . listWidget .= newList
uiState . uiGameplay . uiDialogs . uiGoal . listWidget .= newList
GoalSummary -> handleInfoPanelEvent modalScroll (VtyEvent ev)
_ -> handleInfoPanelEvent modalScroll (VtyEvent ev)
Just StructuresModal -> case ev of
V.EvKey (V.KChar '\t') [] -> uiState . uiGameplay . uiStructure . structurePanelFocus %= focusNext
V.EvKey (V.KChar '\t') [] -> uiState . uiGameplay . uiDialogs . uiStructure . structurePanelFocus %= focusNext
_ -> do
focused <- use $ uiState . uiGameplay . uiStructure . structurePanelFocus
focused <- use $ uiState . uiGameplay . uiDialogs . uiStructure . structurePanelFocus
case focusGetCurrent focused of
Just (StructureWidgets w) -> case w of
StructuresList ->
refreshList $ uiState . uiGameplay . uiStructure . structurePanelListWidget
refreshList $ uiState . uiGameplay . uiDialogs . uiStructure . structurePanelListWidget
StructureSummary -> handleInfoPanelEvent modalScroll (VtyEvent ev)
_ -> handleInfoPanelEvent modalScroll (VtyEvent ev)
_ -> handleInfoPanelEvent modalScroll (VtyEvent ev)
Expand Down
4 changes: 2 additions & 2 deletions src/swarm-tui/Swarm/TUI/Controller/EventHandlers/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -88,7 +88,7 @@ toggleMessagesModal = do
viewGoal :: EventM Name AppState ()
viewGoal = do
s <- get
if hasAnythingToShow $ s ^. uiState . uiGameplay . uiGoal . goalsContent
if hasAnythingToShow $ s ^. uiState . uiGameplay . uiDialogs . uiGoal . goalsContent
then toggleModal GoalModal
else continueWithoutRedraw

Expand Down Expand Up @@ -144,7 +144,7 @@ toggleREPLVisibility = do

isRunning :: EventM Name AppState Bool
isRunning = do
mt <- preuse $ uiState . uiGameplay . uiModal . _Just . modalType
mt <- preuse $ uiState . uiGameplay . uiDialogs . uiModal . _Just . modalType
return $ maybe True isRunningModal mt

whenRunning :: EventM Name AppState () -> EventM Name AppState ()
Expand Down
2 changes: 1 addition & 1 deletion src/swarm-tui/Swarm/TUI/Controller/EventHandlers/Robot.hs
Original file line number Diff line number Diff line change
Expand Up @@ -69,7 +69,7 @@ showEntityDescription = gets focusedEntity >>= maybe continueWithoutRedraw descr
descriptionModal e = do
s <- get
resetViewport modalScroll
uiState . uiGameplay . uiModal ?= generateModal s (DescriptionModal e)
uiState . uiGameplay . uiDialogs . uiModal ?= generateModal s (DescriptionModal e)

-- | Attempt to make an entity selected from the inventory, if the
-- base is not currently busy.
Expand Down
6 changes: 3 additions & 3 deletions src/swarm-tui/Swarm/TUI/Controller/UpdateUI.hs
Original file line number Diff line number Diff line change
Expand Up @@ -188,7 +188,7 @@ updateUI = do
-- * shows the player more "optional" goals they can continue to pursue
doGoalUpdates :: EventM Name AppState Bool
doGoalUpdates = do
curGoal <- use (uiState . uiGameplay . uiGoal . goalsContent)
curGoal <- use (uiState . uiGameplay . uiDialogs . uiGoal . goalsContent)
curWinCondition <- use (gameState . winCondition)
announcementsSeq <- use (gameState . messageInfo . announcementQueue)
let announcementsList = toList announcementsSeq
Expand Down Expand Up @@ -218,7 +218,7 @@ doGoalUpdates = do
return True
WinConditions _ oc -> do
showHiddenGoals <- use $ uiState . uiDebugOptions . Lens.contains ShowHiddenGoals
currentModal <- preuse $ uiState . uiGameplay . uiModal . _Just . modalType
currentModal <- preuse $ uiState . uiGameplay . uiDialogs . uiModal . _Just . modalType
let newGoalTracking = GoalTracking announcementsList $ constructGoalMap showHiddenGoals oc
-- The "uiGoal" field is initialized with empty members, so we know that
-- this will be the first time showing it if it will be nonempty after previously
Expand All @@ -232,7 +232,7 @@ doGoalUpdates = do
when (goalWasUpdated && not isEnding) $ do
-- The "uiGoal" field is necessary at least to "persist" the data that is needed
-- if the player chooses to later "recall" the goals dialog with CTRL+g.
uiState . uiGameplay . uiGoal .= goalDisplay newGoalTracking
uiState . uiGameplay . uiDialogs . uiGoal .= goalDisplay newGoalTracking

-- This clears the "flag" that indicate that the goals dialog needs to be
-- automatically popped up.
Expand Down
6 changes: 3 additions & 3 deletions src/swarm-tui/Swarm/TUI/Controller/Util.hs
Original file line number Diff line number Diff line change
Expand Up @@ -76,7 +76,7 @@ openModal mt = do
resetViewport modalScroll
newModal <- gets $ flip generateModal mt
ensurePause
uiState . uiGameplay . uiModal ?= newModal
uiState . uiGameplay . uiDialogs . uiModal ?= newModal
-- Beep
case mt of
ScenarioEndModal _ -> do
Expand Down Expand Up @@ -121,10 +121,10 @@ safeAutoUnpause = do

toggleModal :: ModalType -> EventM Name AppState ()
toggleModal mt = do
modal <- use $ uiState . uiGameplay . uiModal
modal <- use $ uiState . uiGameplay . uiDialogs . uiModal
case modal of
Nothing -> openModal mt
Just _ -> uiState . uiGameplay . uiModal .= Nothing >> safeAutoUnpause
Just _ -> uiState . uiGameplay . uiDialogs . uiModal .= Nothing >> safeAutoUnpause

setFocus :: FocusablePanel -> EventM Name AppState ()
setFocus name = uiState . uiGameplay . uiFocusRing %= focusSetCurrent (FocusablePanel name)
Expand Down
4 changes: 2 additions & 2 deletions src/swarm-tui/Swarm/TUI/Model/StateUpdate.hs
Original file line number Diff line number Diff line change
Expand Up @@ -257,7 +257,7 @@ scenarioToUIState isAutoplaying siPair@(scenario, _) gs u = do
fst siPair ^. scenarioLandscape . scenarioAttrs
)
swarmAttrMap
& uiGameplay . uiGoal .~ emptyGoalDisplay
& uiGameplay . uiDialogs . uiGoal .~ emptyGoalDisplay
& uiGameplay . uiIsAutoPlay .~ isAutoplaying
& uiGameplay . uiFocusRing .~ initFocusRing
& uiGameplay . uiInventory . uiInventorySearch .~ Nothing
Expand All @@ -271,7 +271,7 @@ scenarioToUIState isAutoplaying siPair@(scenario, _) gs u = do
& uiGameplay . uiTiming . lastFrameTime .~ curTime
& uiGameplay . uiWorldEditor . EM.entityPaintList %~ BL.listReplace entityList Nothing
& uiGameplay . uiWorldEditor . EM.editingBounds . EM.boundsRect %~ setNewBounds
& uiGameplay . uiStructure
& uiGameplay . uiDialogs . uiStructure
.~ StructureDisplay
(SR.makeListWidget . M.elems $ gs ^. discovery . structureRecognition . automatons . originalStructureDefinitions)
(focusSetCurrent (StructureWidgets StructuresList) $ focusRing $ map StructureWidgets enumerate)
Expand Down
48 changes: 32 additions & 16 deletions src/swarm-tui/Swarm/TUI/Model/UI.hs
Original file line number Diff line number Diff line change
Expand Up @@ -31,6 +31,7 @@ module Swarm.TUI.Model.UI (
uiModal,
uiGoal,
uiStructure,
uiDialogs,
uiIsAutoPlay,
uiAchievements,
lgTicksPerSecond,
Expand Down Expand Up @@ -194,6 +195,28 @@ uiShowZero :: Lens' UIInventory Bool
-- | Whether the Inventory ui panel should update
uiInventoryShouldUpdate :: Lens' UIInventory Bool

-- | State that backs various modal dialogs
data UIDialogs = UIDialogs
{ _uiModal :: Maybe Modal
, _uiGoal :: GoalDisplay
, _uiStructure :: StructureDisplay
}

-- * Lenses for UIDialogs

makeLensesNoSigs ''UIDialogs

-- | When this is 'Just', it represents a modal to be displayed on
-- top of the UI, e.g. for the Help screen.
uiModal :: Lens' UIDialogs (Maybe Modal)

-- | Status of the scenario goal: whether there is one, and whether it
-- has been displayed to the user initially.
uiGoal :: Lens' UIDialogs GoalDisplay

-- | Definition and status of a recognizable structure
uiStructure :: Lens' UIDialogs StructureDisplay

-- | The main record holding the gameplay UI state. For access to the fields,
-- see the lenses below.
data UIGameplay = UIGameplay
Expand All @@ -203,9 +226,7 @@ data UIGameplay = UIGameplay
, _uiREPL :: REPLState
, _uiInventory :: UIInventory
, _uiScrollToEnd :: Bool
, _uiModal :: Maybe Modal
, _uiGoal :: GoalDisplay
, _uiStructure :: StructureDisplay
, _uiDialogs :: UIDialogs
, _uiIsAutoPlay :: Bool
, _uiShowREPL :: Bool
, _uiShowDebug :: Bool
Expand Down Expand Up @@ -241,16 +262,8 @@ uiREPL :: Lens' UIGameplay REPLState
-- (used when a new log message is appended).
uiScrollToEnd :: Lens' UIGameplay Bool

-- | When this is 'Just', it represents a modal to be displayed on
-- top of the UI, e.g. for the Help screen.
uiModal :: Lens' UIGameplay (Maybe Modal)

-- | Status of the scenario goal: whether there is one, and whether it
-- has been displayed to the user initially.
uiGoal :: Lens' UIGameplay GoalDisplay

-- | Definition and status of a recognizable structure
uiStructure :: Lens' UIGameplay StructureDisplay
-- | State that backs various modal dialogs
uiDialogs :: Lens' UIGameplay UIDialogs

-- | When running with @--autoplay@, suppress the goal dialogs.
--
Expand Down Expand Up @@ -379,9 +392,12 @@ initUIState speedFactor showMainMenu debug = do
, _uiInventoryShouldUpdate = False
}
, _uiScrollToEnd = False
, _uiModal = Nothing
, _uiGoal = emptyGoalDisplay
, _uiStructure = emptyStructureDisplay
, _uiDialogs =
UIDialogs
{ _uiModal = Nothing
, _uiGoal = emptyGoalDisplay
, _uiStructure = emptyStructureDisplay
}
, _uiIsAutoPlay = False
, _uiTiming =
UITiming
Expand Down
10 changes: 5 additions & 5 deletions src/swarm-tui/Swarm/TUI/View.hs
Original file line number Diff line number Diff line change
Expand Up @@ -613,13 +613,13 @@ replHeight = 10

-- | Hide the cursor when a modal is set
chooseCursor :: AppState -> [CursorLocation n] -> Maybe (CursorLocation n)
chooseCursor s locs = case s ^. uiState . uiGameplay . uiModal of
chooseCursor s locs = case s ^. uiState . uiGameplay . uiDialogs . uiModal of
Nothing -> showFirstCursor s locs
Just _ -> Nothing

-- | Draw a dialog window, if one should be displayed right now.
drawDialog :: AppState -> Widget Name
drawDialog s = case s ^. uiState . uiGameplay . uiModal of
drawDialog s = case s ^. uiState . uiGameplay . uiDialogs . uiModal of
Just (Modal mt d) -> renderDialog d $ case mt of
GoalModal -> drawModal s mt
_ -> maybeScroll ModalViewport $ drawModal s mt
Expand All @@ -633,7 +633,7 @@ drawModal s = \case
RecipesModal -> availableListWidget (s ^. gameState) RecipeList
CommandsModal -> commandsListWidget (s ^. gameState)
MessagesModal -> availableListWidget (s ^. gameState) MessageList
StructuresModal -> SR.renderStructuresDisplay (s ^. gameState) (s ^. uiState . uiGameplay . uiStructure)
StructuresModal -> SR.renderStructuresDisplay (s ^. gameState) (s ^. uiState . uiGameplay . uiDialogs . uiStructure)
ScenarioEndModal outcome ->
padBottom (Pad 1) $
vBox $
Expand All @@ -650,7 +650,7 @@ drawModal s = \case
DescriptionModal e -> descriptionWidget s e
QuitModal -> padBottom (Pad 1) $ hCenter $ txt (quitMsg (s ^. uiState . uiMenu))
GoalModal ->
GR.renderGoalsDisplay (s ^. uiState . uiGameplay . uiGoal) $
GR.renderGoalsDisplay (s ^. uiState . uiGameplay . uiDialogs . uiGoal) $
view (scenarioOperation . scenarioDescription) . fst <$> s ^. uiState . uiGameplay . scenarioRef
KeepPlayingModal ->
padLeftRight 1 $
Expand Down Expand Up @@ -1013,7 +1013,7 @@ drawKeyMenu s =
creative = s ^. gameState . creativeMode
showCreative = s ^. uiState . uiDebugOptions . Lens.contains ToggleCreative
showEditor = s ^. uiState . uiDebugOptions . Lens.contains ToggleWorldEditor
goal = hasAnythingToShow $ s ^. uiState . uiGameplay . uiGoal . goalsContent
goal = hasAnythingToShow $ s ^. uiState . uiGameplay . uiDialogs . uiGoal . goalsContent
showZero = s ^. uiState . uiGameplay . uiInventory . uiShowZero
inventorySort = s ^. uiState . uiGameplay . uiInventory . uiInventorySort
inventorySearch = s ^. uiState . uiGameplay . uiInventory . uiInventorySearch
Expand Down
2 changes: 1 addition & 1 deletion src/swarm-web/Swarm/Web.hs
Original file line number Diff line number Diff line change
Expand Up @@ -200,7 +200,7 @@ goalsGraphHandler appStateRef = do
uiGoalHandler :: IO AppState -> Handler GoalTracking
uiGoalHandler appStateRef = do
appState <- liftIO appStateRef
return $ appState ^. uiState . uiGameplay . uiGoal . goalsContent
return $ appState ^. uiState . uiGameplay . uiDialogs . uiGoal . goalsContent

goalsHandler :: IO AppState -> Handler WinCondition
goalsHandler appStateRef = do
Expand Down

0 comments on commit 162aee8

Please sign in to comment.