Skip to content

Commit

Permalink
Fix dialog controls
Browse files Browse the repository at this point in the history
  • Loading branch information
kostmo committed Sep 15, 2024
1 parent f70666b commit cbaaf22
Show file tree
Hide file tree
Showing 5 changed files with 51 additions and 33 deletions.
1 change: 1 addition & 0 deletions src/swarm-tournament/Swarm/Web/Tournament.hs
Original file line number Diff line number Diff line change
Expand Up @@ -368,6 +368,7 @@ app unitTestFileserver appData =
-- files there.
-- Instead, we manually stub the paths that are used as redirects
-- so that the web API invocation does not 404 when looking for them.

serveDirectoryEmbedded
[ (TL.unpack defaultRedirectPage, "Hello World!")
, (TL.unpack defaultSolutionSubmissionRedirectPage, "Hello World!")
Expand Down
52 changes: 33 additions & 19 deletions src/swarm-tui/Swarm/TUI/Controller.hs
Original file line number Diff line number Diff line change
Expand Up @@ -296,7 +296,11 @@ 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 . uiDialogs . uiModal -> closeModal m
EscapeKey
| Just m <- s ^. uiState . uiGameplay . uiDialogs . uiModal ->
if s ^. uiState . uiGameplay . uiDialogs . uiRobot . isDetailsOpened
then uiState . uiGameplay . uiDialogs . uiRobot . isDetailsOpened .= False
else closeModal m
-- Pass to key handler (allows users to configure bindings)
-- See Note [how Swarm event handlers work]
VtyEvent (V.EvKey k m)
Expand Down Expand Up @@ -379,19 +383,30 @@ closeModal m = do
handleModalEvent :: V.Event -> EventM Name AppState ()
handleModalEvent = \case
V.EvKey V.KEnter [] -> do
mdialog <- preuse $ uiState . uiGameplay . uiDialogs . uiModal . _Just . modalDialog
toggleModal QuitModal
case dialogSelection =<< mdialog of
Just (Button QuitButton, _) -> quitGame
Just (Button KeepPlayingButton, _) -> toggleModal KeepPlayingModal
Just (Button StartOverButton, StartOver currentSeed siPair) -> do
invalidateCache
restartGame currentSeed siPair
Just (Button NextButton, Next siPair) -> do
quitGame
invalidateCache
startGame siPair Nothing
_ -> return ()
modal <- preuse $ uiState . uiGameplay . uiDialogs . uiModal . _Just . modalType
case modal of
Just RobotsModal -> do
robotDialog <- use $ uiState . uiGameplay . uiDialogs . uiRobot
unless (robotDialog ^. isDetailsOpened) $ do
let widget = robotDialog ^. robotListContent . robotsListWidget
forM_ (BL.listSelectedElement $ getList widget) $ \x -> do
Brick.zoom (uiState . uiGameplay . uiDialogs . uiRobot) $ do
isDetailsOpened .= True
updateRobotDetailsPane $ snd x
_ -> do
mdialog <- preuse $ uiState . uiGameplay . uiDialogs . uiModal . _Just . modalDialog
toggleModal QuitModal
case dialogSelection =<< mdialog of
Just (Button QuitButton, _) -> quitGame
Just (Button KeepPlayingButton, _) -> toggleModal KeepPlayingModal
Just (Button StartOverButton, StartOver currentSeed siPair) -> do
invalidateCache
restartGame currentSeed siPair
Just (Button NextButton, Next siPair) -> do
quitGame
invalidateCache
startGame siPair Nothing
_ -> return ()
ev -> do
Brick.zoom (uiState . uiGameplay . uiDialogs . uiModal . _Just . modalDialog) (handleDialogEvent ev)
modal <- preuse $ uiState . uiGameplay . uiDialogs . uiModal . _Just . modalType
Expand Down Expand Up @@ -425,11 +440,10 @@ handleModalEvent = \case
Just RobotsModal -> Brick.zoom (uiState . uiGameplay . uiDialogs . uiRobot) $ case ev of
V.EvKey (V.KChar '\t') [] -> robotDetailsFocus %= focusNext
_ -> do
foc <- use robotDetailsFocus
case focusGetCurrent foc of
(Just (RobotsListDialog (SingleRobotDetails RobotLogPane))) ->
Brick.zoom (robotListContent . robotDetailsPaneState . logsList) $ handleListEvent ev
_ -> do
isInDetailsMode <- use isDetailsOpened
if isInDetailsMode
then Brick.zoom (robotListContent . robotDetailsPaneState . logsList) $ handleListEvent ev
else do
Brick.zoom (robotListContent . robotsListWidget) $
handleMixedListEvent ev

Expand Down
3 changes: 2 additions & 1 deletion src/swarm-tui/Swarm/TUI/Model/UI.hs
Original file line number Diff line number Diff line change
Expand Up @@ -173,7 +173,8 @@ initUIState UIInitOptions {..} = do
, _uiStructure = emptyStructureDisplay
, _uiRobot =
RobotDisplay
{ _robotDetailsFocus = focusRing $ map RobotsListDialog $ RobotList : map SingleRobotDetails enumerate
{ _robotDetailsFocus = focusRing $ map (RobotsListDialog . SingleRobotDetails) enumerate
, _isDetailsOpened = False
, _robotListContent = emptyRobotDisplay debugOptions
}
}
Expand Down
27 changes: 14 additions & 13 deletions src/swarm-tui/Swarm/TUI/View/Robot.hs
Original file line number Diff line number Diff line change
Expand Up @@ -19,7 +19,6 @@ module Swarm.TUI.View.Robot (
) where

import Brick
import Brick.Focus
import Brick.Widgets.Border
import Brick.Widgets.List qualified as BL
import Brick.Widgets.TabularList.Mixed
Expand Down Expand Up @@ -385,18 +384,20 @@ mkLibraryEntries c =

drawRobotsModal :: RobotDisplay -> Widget Name
drawRobotsModal robotDialog =
vBox
[ mainContent
, tabControlFooter
]
mainContent
where
rFocusRing = robotDialog ^. robotDetailsFocus

mainContent = case focusGetCurrent rFocusRing of
Just (RobotsListDialog (SingleRobotDetails _)) -> case maybeSelectedRobot of
Nothing -> str "No selection"
Just r -> renderRobotDetails rFocusRing r $ robotDialog ^. robotListContent . robotDetailsPaneState
where
oldList = getList $ robotDialog ^. robotListContent . robotsListWidget
maybeSelectedRobot = view robot . snd <$> BL.listSelectedElement oldList
_ -> renderRobotsList $ robotDialog ^. robotListContent
mainContent =
if robotDialog ^. isDetailsOpened
then
let oldList = getList $ robotDialog ^. robotListContent . robotsListWidget
maybeSelectedRobot = view robot . snd <$> BL.listSelectedElement oldList
detailsContent = case maybeSelectedRobot of
Nothing -> str "No selection"
Just r -> renderRobotDetails rFocusRing r $ robotDialog ^. robotListContent . robotDetailsPaneState
in vBox
[ detailsContent
, tabControlFooter
]
else renderRobotsList $ robotDialog ^. robotListContent
1 change: 1 addition & 0 deletions src/swarm-tui/Swarm/TUI/View/Robot/Type.hs
Original file line number Diff line number Diff line change
Expand Up @@ -86,6 +86,7 @@ makeLenses ''RobotListContent

data RobotDisplay = RobotDisplay
{ _robotDetailsFocus :: FocusRing Name
, _isDetailsOpened :: Bool
, _robotListContent :: RobotListContent
}

Expand Down

0 comments on commit cbaaf22

Please sign in to comment.