mirror of
https://github.com/swarm-game/swarm.git
synced 2025-01-07 16:55:59 +03:00
Group modal dialog states into a record (#2139)
A refactoring towards #2138 A new field for the robots dialog will be added to the `UIDialogs` record next. Also, move F2 robots dialog rendering code to a new module `Swarm.TUI.View.Robot`.
This commit is contained in:
parent
413a714e84
commit
4721f9021f
@ -96,12 +96,10 @@ import Swarm.TUI.Launch.Model
|
||||
import Swarm.TUI.Launch.Prep (prepareLaunchDialog)
|
||||
import Swarm.TUI.List
|
||||
import Swarm.TUI.Model
|
||||
import Swarm.TUI.Model.Goal
|
||||
import Swarm.TUI.Model.Dialog
|
||||
import Swarm.TUI.Model.Name
|
||||
import Swarm.TUI.Model.Popup (progressPopups)
|
||||
import Swarm.TUI.Model.Repl
|
||||
import Swarm.TUI.Model.StateUpdate
|
||||
import Swarm.TUI.Model.Structure
|
||||
import Swarm.TUI.Model.UI
|
||||
import Swarm.Util hiding (both, (<<.=))
|
||||
|
||||
@ -294,14 +292,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 _ _ ->
|
||||
@ -367,7 +365,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
|
||||
@ -377,7 +375,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
|
||||
@ -391,33 +389,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)
|
||||
|
@ -24,8 +24,8 @@ import Swarm.TUI.Controller.Util
|
||||
import Swarm.TUI.Editor.Model (isWorldEditorEnabled, worldOverdraw)
|
||||
import Swarm.TUI.Model
|
||||
import Swarm.TUI.Model.DebugOption (DebugOption (ToggleCreative, ToggleWorldEditor))
|
||||
import Swarm.TUI.Model.Dialog.Goal
|
||||
import Swarm.TUI.Model.Event (MainEvent (..), SwarmEvent (..))
|
||||
import Swarm.TUI.Model.Goal
|
||||
import Swarm.TUI.Model.UI
|
||||
import System.Clock (Clock (..), TimeSpec (..), getTime)
|
||||
|
||||
@ -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
|
||||
|
||||
@ -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 ()
|
||||
|
@ -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.
|
||||
|
@ -37,9 +37,9 @@ import Swarm.TUI.Controller.SaveScenario (saveScenarioInfoOnFinishNocheat)
|
||||
import Swarm.TUI.Controller.Util
|
||||
import Swarm.TUI.Model
|
||||
import Swarm.TUI.Model.DebugOption (DebugOption (..))
|
||||
import Swarm.TUI.Model.Goal
|
||||
import Swarm.TUI.Model.Dialog.Goal
|
||||
import Swarm.TUI.Model.Dialog.Popup (Popup (..), addPopup)
|
||||
import Swarm.TUI.Model.Name
|
||||
import Swarm.TUI.Model.Popup (Popup (..), addPopup)
|
||||
import Swarm.TUI.Model.Repl
|
||||
import Swarm.TUI.Model.UI
|
||||
import Swarm.TUI.View.Objective qualified as GR
|
||||
@ -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
|
||||
@ -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
|
||||
@ -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.
|
||||
|
@ -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
|
||||
@ -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)
|
||||
|
@ -19,7 +19,7 @@ import Swarm.Game.Achievement.Attainment
|
||||
import Swarm.Game.Achievement.Definitions
|
||||
import Swarm.Game.Achievement.Persistence
|
||||
import Swarm.TUI.Model
|
||||
import Swarm.TUI.Model.Popup (Popup (AchievementPopup), addPopup)
|
||||
import Swarm.TUI.Model.Dialog.Popup (Popup (AchievementPopup), addPopup)
|
||||
import Swarm.TUI.Model.UI
|
||||
|
||||
attainAchievement :: (MonadIO m, MonadState AppState m) => CategorizedAchievement -> m ()
|
||||
|
9
src/swarm-tui/Swarm/TUI/Model/Dialog.hs
Normal file
9
src/swarm-tui/Swarm/TUI/Model/Dialog.hs
Normal file
@ -0,0 +1,9 @@
|
||||
module Swarm.TUI.Model.Dialog (
|
||||
module Swarm.TUI.Model.Dialog.Goal,
|
||||
module Swarm.TUI.Model.Dialog.Popup,
|
||||
module Swarm.TUI.Model.Dialog.Structure,
|
||||
) where
|
||||
|
||||
import Swarm.TUI.Model.Dialog.Goal
|
||||
import Swarm.TUI.Model.Dialog.Popup
|
||||
import Swarm.TUI.Model.Dialog.Structure
|
@ -5,7 +5,7 @@
|
||||
-- SPDX-License-Identifier: BSD-3-Clause
|
||||
--
|
||||
-- A UI-centric model for Objective presentation.
|
||||
module Swarm.TUI.Model.Goal where
|
||||
module Swarm.TUI.Model.Dialog.Goal where
|
||||
|
||||
import Brick.Focus
|
||||
import Brick.Widgets.List qualified as BL
|
@ -1,7 +1,7 @@
|
||||
{-# LANGUAGE PatternSynonyms #-}
|
||||
{-# LANGUAGE TemplateHaskell #-}
|
||||
|
||||
module Swarm.TUI.Model.Popup (
|
||||
module Swarm.TUI.Model.Dialog.Popup (
|
||||
-- * Popup types
|
||||
Popup (..),
|
||||
|
@ -5,7 +5,7 @@
|
||||
-- SPDX-License-Identifier: BSD-3-Clause
|
||||
--
|
||||
-- A UI-centric model for Structure presentation.
|
||||
module Swarm.TUI.Model.Structure where
|
||||
module Swarm.TUI.Model.Dialog.Structure where
|
||||
|
||||
import Brick.Focus
|
||||
import Brick.Widgets.List qualified as BL
|
@ -82,11 +82,10 @@ import Swarm.TUI.Launch.Model (toSerializableParams)
|
||||
import Swarm.TUI.Model
|
||||
import Swarm.TUI.Model.Achievements
|
||||
import Swarm.TUI.Model.DebugOption (DebugOption (LoadTestingScenarios))
|
||||
import Swarm.TUI.Model.Goal (emptyGoalDisplay)
|
||||
import Swarm.TUI.Model.Dialog
|
||||
import Swarm.TUI.Model.KeyBindings
|
||||
import Swarm.TUI.Model.Name
|
||||
import Swarm.TUI.Model.Repl
|
||||
import Swarm.TUI.Model.Structure
|
||||
import Swarm.TUI.Model.UI
|
||||
import Swarm.TUI.View.Attribute.Attr (getWorldAttrName, swarmAttrMap)
|
||||
import Swarm.TUI.View.Attribute.CustomStyling (toAttrPair)
|
||||
@ -257,7 +256,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
|
||||
@ -271,7 +270,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)
|
||||
|
@ -31,6 +31,7 @@ module Swarm.TUI.Model.UI (
|
||||
uiModal,
|
||||
uiGoal,
|
||||
uiStructure,
|
||||
uiDialogs,
|
||||
uiIsAutoPlay,
|
||||
uiAchievements,
|
||||
lgTicksPerSecond,
|
||||
@ -88,12 +89,10 @@ import Swarm.TUI.Inventory.Sorting
|
||||
import Swarm.TUI.Launch.Model
|
||||
import Swarm.TUI.Launch.Prep
|
||||
import Swarm.TUI.Model.DebugOption (DebugOption)
|
||||
import Swarm.TUI.Model.Goal
|
||||
import Swarm.TUI.Model.Dialog
|
||||
import Swarm.TUI.Model.Menu
|
||||
import Swarm.TUI.Model.Name
|
||||
import Swarm.TUI.Model.Popup
|
||||
import Swarm.TUI.Model.Repl
|
||||
import Swarm.TUI.Model.Structure
|
||||
import Swarm.TUI.View.Attribute.Attr (swarmAttrMap)
|
||||
import Swarm.Util
|
||||
import Swarm.Util.Lens (makeLensesExcluding, makeLensesNoSigs)
|
||||
@ -194,6 +193,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
|
||||
@ -203,9 +224,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
|
||||
@ -241,16 +260,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.
|
||||
--
|
||||
@ -379,9 +390,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
|
||||
|
@ -54,7 +54,6 @@ import Data.Bits (shiftL, shiftR, (.&.))
|
||||
import Data.Foldable (toList)
|
||||
import Data.Foldable qualified as F
|
||||
import Data.Functor (($>))
|
||||
import Data.IntMap qualified as IM
|
||||
import Data.List (intersperse)
|
||||
import Data.List qualified as L
|
||||
import Data.List.Extra (enumerate)
|
||||
@ -69,11 +68,8 @@ import Data.Set qualified as Set (toList)
|
||||
import Data.Text (Text)
|
||||
import Data.Text qualified as T
|
||||
import Data.Time (NominalDiffTime, defaultTimeLocale, formatTime)
|
||||
import Linear
|
||||
import Network.Wai.Handler.Warp (Port)
|
||||
import Numeric (showFFloat)
|
||||
import Swarm.Constant
|
||||
import Swarm.Game.CESK (CESK (..))
|
||||
import Swarm.Game.Device (commandCost, commandsForDeviceCaps, enabledCommands, getMap, ingredients)
|
||||
import Swarm.Game.Display
|
||||
import Swarm.Game.Entity as E
|
||||
@ -82,7 +78,6 @@ import Swarm.Game.Land
|
||||
import Swarm.Game.Location
|
||||
import Swarm.Game.Recipe
|
||||
import Swarm.Game.Robot
|
||||
import Swarm.Game.Robot.Activity
|
||||
import Swarm.Game.Robot.Concrete
|
||||
import Swarm.Game.Scenario (
|
||||
scenarioAuthor,
|
||||
@ -114,7 +109,7 @@ import Swarm.Game.State.Landscape
|
||||
import Swarm.Game.State.Robot
|
||||
import Swarm.Game.State.Runtime
|
||||
import Swarm.Game.State.Substate
|
||||
import Swarm.Game.Tick (TickNumber (..), addTicks)
|
||||
import Swarm.Game.Tick (TickNumber (..))
|
||||
import Swarm.Game.Universe
|
||||
import Swarm.Game.World.Coords
|
||||
import Swarm.Game.World.Gen (Seed)
|
||||
@ -134,8 +129,8 @@ import Swarm.TUI.Launch.Model
|
||||
import Swarm.TUI.Launch.View
|
||||
import Swarm.TUI.Model
|
||||
import Swarm.TUI.Model.DebugOption (DebugOption (..))
|
||||
import Swarm.TUI.Model.Dialog.Goal (goalsContent, hasAnythingToShow)
|
||||
import Swarm.TUI.Model.Event qualified as SE
|
||||
import Swarm.TUI.Model.Goal (goalsContent, hasAnythingToShow)
|
||||
import Swarm.TUI.Model.KeyBindings (handlerNameKeysDescription)
|
||||
import Swarm.TUI.Model.Repl
|
||||
import Swarm.TUI.Model.UI
|
||||
@ -146,12 +141,10 @@ import Swarm.TUI.View.CellDisplay
|
||||
import Swarm.TUI.View.Logo
|
||||
import Swarm.TUI.View.Objective qualified as GR
|
||||
import Swarm.TUI.View.Popup
|
||||
import Swarm.TUI.View.Robot
|
||||
import Swarm.TUI.View.Structure qualified as SR
|
||||
import Swarm.TUI.View.Util as VU
|
||||
import Swarm.Util
|
||||
import Swarm.Util.UnitInterval
|
||||
import Swarm.Util.WindowedCounter qualified as WC
|
||||
import System.Clock (TimeSpec (..))
|
||||
import Text.Printf
|
||||
import Text.Wrap
|
||||
import Witch (into)
|
||||
@ -507,14 +500,6 @@ drawGameUI s =
|
||||
)
|
||||
]
|
||||
|
||||
renderCoordsString :: Cosmic Location -> String
|
||||
renderCoordsString (Cosmic sw coords) =
|
||||
unwords $ VU.locationToString coords : suffix
|
||||
where
|
||||
suffix = case sw of
|
||||
DefaultRootSubworld -> []
|
||||
SubworldName swName -> ["in", T.unpack swName]
|
||||
|
||||
drawWorldCursorInfo :: WorldOverdraw -> GameState -> Cosmic Coords -> Widget Name
|
||||
drawWorldCursorInfo worldEditor g cCoords =
|
||||
case getStatic g coords of
|
||||
@ -613,13 +598,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
|
||||
@ -633,7 +618,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 $
|
||||
@ -650,7 +635,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 $
|
||||
@ -660,133 +645,6 @@ drawModal s = \case
|
||||
TerrainPaletteModal -> EV.drawTerrainSelector s
|
||||
EntityPaletteModal -> EV.drawEntityPaintSelector s
|
||||
|
||||
-- | Render the percentage of ticks that this robot was active.
|
||||
-- This indicator can take some time to "warm up" and stabilize
|
||||
-- due to the sliding window.
|
||||
--
|
||||
-- == Use of previous tick
|
||||
-- The 'Swarm.Game.Step.gameTick' function runs all robots, then increments the current tick.
|
||||
-- So at the time we are rendering a frame, the current tick will always be
|
||||
-- strictly greater than any ticks stored in the 'WC.WindowedCounter' for any robot;
|
||||
-- hence 'WC.getOccupancy' will never be @1@ if we use the current tick directly as
|
||||
-- obtained from the 'ticks' function.
|
||||
-- So we "rewind" it to the previous tick for the purpose of this display.
|
||||
renderDutyCycle :: GameState -> Robot -> Widget Name
|
||||
renderDutyCycle gs robot =
|
||||
withAttr dutyCycleAttr . str . flip (showFFloat (Just 1)) "%" $ dutyCyclePercentage
|
||||
where
|
||||
curTicks = gs ^. temporal . ticks
|
||||
window = robot ^. activityCounts . activityWindow
|
||||
|
||||
-- Rewind to previous tick
|
||||
latestRobotTick = addTicks (-1) curTicks
|
||||
dutyCycleRatio = WC.getOccupancy latestRobotTick window
|
||||
|
||||
dutyCycleAttr = safeIndex dutyCycleRatio meterAttributeNames
|
||||
|
||||
dutyCyclePercentage :: Double
|
||||
dutyCyclePercentage = 100 * getValue dutyCycleRatio
|
||||
|
||||
robotsListWidget :: AppState -> Widget Name
|
||||
robotsListWidget s = hCenter table
|
||||
where
|
||||
table =
|
||||
BT.renderTable
|
||||
. BT.columnBorders False
|
||||
. BT.setDefaultColAlignment BT.AlignCenter
|
||||
-- Inventory count is right aligned
|
||||
. BT.alignRight 4
|
||||
. BT.table
|
||||
$ map (padLeftRight 1) <$> (headers : robotsTable)
|
||||
headings =
|
||||
[ "Name"
|
||||
, "Age"
|
||||
, "Pos"
|
||||
, "Items"
|
||||
, "Status"
|
||||
, "Actns"
|
||||
, "Cmds"
|
||||
, "Cycles"
|
||||
, "Activity"
|
||||
, "Log"
|
||||
]
|
||||
headers = withAttr robotAttr . txt <$> applyWhen debugRID ("ID" :) headings
|
||||
robotsTable = mkRobotRow <$> robots
|
||||
mkRobotRow robot =
|
||||
applyWhen debugRID (idWidget :) cells
|
||||
where
|
||||
cells =
|
||||
[ nameWidget
|
||||
, str ageStr
|
||||
, locWidget
|
||||
, padRight (Pad 1) (str $ show rInvCount)
|
||||
, statusWidget
|
||||
, str $ show $ robot ^. activityCounts . tangibleCommandCount
|
||||
, -- TODO(#1341): May want to expose the details of this histogram in
|
||||
-- a per-robot pop-up
|
||||
str . show . sum . M.elems $ robot ^. activityCounts . commandsHistogram
|
||||
, str $ show $ robot ^. activityCounts . lifetimeStepCount
|
||||
, renderDutyCycle (s ^. gameState) robot
|
||||
, txt rLog
|
||||
]
|
||||
|
||||
idWidget = str $ show $ robot ^. robotID
|
||||
nameWidget =
|
||||
hBox
|
||||
[ renderDisplay (robot ^. robotDisplay)
|
||||
, highlightSystem . txt $ " " <> robot ^. robotName
|
||||
]
|
||||
|
||||
highlightSystem = if robot ^. systemRobot then withAttr highlightAttr else id
|
||||
|
||||
ageStr
|
||||
| age < 60 = show age <> "sec"
|
||||
| age < 3600 = show (age `div` 60) <> "min"
|
||||
| age < 3600 * 24 = show (age `div` 3600) <> "hour"
|
||||
| otherwise = show (age `div` 3600 * 24) <> "day"
|
||||
where
|
||||
TimeSpec createdAtSec _ = robot ^. robotCreatedAt
|
||||
TimeSpec nowSec _ = s ^. uiState . uiGameplay . uiTiming . lastFrameTime
|
||||
age = nowSec - createdAtSec
|
||||
|
||||
rInvCount = sum $ map fst . E.elems $ robot ^. robotEntity . entityInventory
|
||||
rLog
|
||||
| robot ^. robotLogUpdated = "x"
|
||||
| otherwise = " "
|
||||
|
||||
locWidget = hBox [worldCell, str $ " " <> locStr]
|
||||
where
|
||||
rCoords = fmap locToCoords rLoc
|
||||
rLoc = robot ^. robotLocation
|
||||
worldCell =
|
||||
drawLoc
|
||||
(s ^. uiState . uiGameplay)
|
||||
g
|
||||
rCoords
|
||||
locStr = renderCoordsString rLoc
|
||||
|
||||
statusWidget = case robot ^. machine of
|
||||
Waiting {} -> txt "waiting"
|
||||
_
|
||||
| isActive robot -> withAttr notifAttr $ txt "busy"
|
||||
| otherwise -> withAttr greenAttr $ txt "idle"
|
||||
|
||||
basePos :: Point V2 Double
|
||||
basePos = realToFrac <$> fromMaybe origin (g ^? baseRobot . robotLocation . planar)
|
||||
-- Keep the base and non system robot (e.g. no seed)
|
||||
isRelevant robot = robot ^. robotID == 0 || not (robot ^. systemRobot)
|
||||
-- Keep the robot that are less than 32 unit away from the base
|
||||
isNear robot = creative || distance (realToFrac <$> robot ^. robotLocation . planar) basePos < 32
|
||||
robots :: [Robot]
|
||||
robots =
|
||||
filter (\robot -> debugAllRobots || (isRelevant robot && isNear robot))
|
||||
. IM.elems
|
||||
$ g ^. robotInfo . robotMap
|
||||
creative = g ^. creativeMode
|
||||
debugRID = s ^. uiState . uiDebugOptions . Lens.contains ListRobotIDs
|
||||
debugAllRobots = s ^. uiState . uiDebugOptions . Lens.contains ListAllRobots
|
||||
g = s ^. gameState
|
||||
|
||||
helpWidget :: Seed -> Maybe Port -> KeyEventHandlingState -> Widget Name
|
||||
helpWidget theSeed mport keyState =
|
||||
padLeftRight 2 . vBox $ padTop (Pad 1) <$> [info, helpKeys, tips]
|
||||
@ -1013,7 +871,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
|
||||
|
@ -20,7 +20,7 @@ import Swarm.Game.Scenario.Objective
|
||||
import Swarm.Language.Syntax (Syntax)
|
||||
import Swarm.Language.Text.Markdown (Document)
|
||||
import Swarm.Language.Text.Markdown qualified as Markdown
|
||||
import Swarm.TUI.Model.Goal
|
||||
import Swarm.TUI.Model.Dialog.Goal
|
||||
import Swarm.TUI.Model.Name
|
||||
import Swarm.TUI.View.Attribute.Attr
|
||||
import Swarm.TUI.View.Util
|
||||
|
@ -15,8 +15,8 @@ import Swarm.Game.Achievement.Definitions (title)
|
||||
import Swarm.Game.Achievement.Description (describe)
|
||||
import Swarm.Language.Syntax (constInfo, syntax)
|
||||
import Swarm.TUI.Model (AppState, Name, uiState)
|
||||
import Swarm.TUI.Model.Dialog.Popup (Popup (..), currentPopup, popupFrames)
|
||||
import Swarm.TUI.Model.Event qualified as SE
|
||||
import Swarm.TUI.Model.Popup (Popup (..), currentPopup, popupFrames)
|
||||
import Swarm.TUI.Model.UI (uiPopups)
|
||||
import Swarm.TUI.View.Attribute.Attr (notifAttr)
|
||||
import Swarm.TUI.View.Util (bindingText)
|
||||
|
167
src/swarm-tui/Swarm/TUI/View/Robot.hs
Normal file
167
src/swarm-tui/Swarm/TUI/View/Robot.hs
Normal file
@ -0,0 +1,167 @@
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{-# LANGUAGE NoGeneralizedNewtypeDeriving #-}
|
||||
|
||||
-- |
|
||||
-- SPDX-License-Identifier: BSD-3-Clause
|
||||
--
|
||||
-- A UI-centric model for presentation of Robot details.
|
||||
module Swarm.TUI.View.Robot where
|
||||
|
||||
import Brick hiding (Direction, Location)
|
||||
import Brick.Widgets.Center (hCenter)
|
||||
import Brick.Widgets.Table qualified as BT
|
||||
import Control.Lens as Lens hiding (Const, from)
|
||||
import Data.IntMap qualified as IM
|
||||
import Data.Map qualified as M
|
||||
import Data.Maybe (fromMaybe)
|
||||
import Linear
|
||||
import Numeric (showFFloat)
|
||||
import Swarm.Game.CESK (CESK (..))
|
||||
import Swarm.Game.Entity as E
|
||||
import Swarm.Game.Location
|
||||
import Swarm.Game.Robot
|
||||
import Swarm.Game.Robot.Activity
|
||||
import Swarm.Game.Robot.Concrete
|
||||
import Swarm.Game.State
|
||||
import Swarm.Game.State.Robot
|
||||
import Swarm.Game.State.Substate
|
||||
import Swarm.Game.Tick (addTicks)
|
||||
import Swarm.Game.Universe
|
||||
import Swarm.Game.World.Coords
|
||||
import Swarm.TUI.Model
|
||||
import Swarm.TUI.Model.DebugOption (DebugOption (..))
|
||||
import Swarm.TUI.Model.UI
|
||||
import Swarm.TUI.View.Attribute.Attr
|
||||
import Swarm.TUI.View.CellDisplay
|
||||
import Swarm.TUI.View.Util as VU
|
||||
import Swarm.Util
|
||||
import Swarm.Util.UnitInterval
|
||||
import Swarm.Util.WindowedCounter qualified as WC
|
||||
import System.Clock (TimeSpec (..))
|
||||
|
||||
-- | Render the percentage of ticks that this robot was active.
|
||||
-- This indicator can take some time to "warm up" and stabilize
|
||||
-- due to the sliding window.
|
||||
--
|
||||
-- == Use of previous tick
|
||||
-- The 'Swarm.Game.Step.gameTick' function runs all robots, then increments the current tick.
|
||||
-- So at the time we are rendering a frame, the current tick will always be
|
||||
-- strictly greater than any ticks stored in the 'WC.WindowedCounter' for any robot;
|
||||
-- hence 'WC.getOccupancy' will never be @1@ if we use the current tick directly as
|
||||
-- obtained from the 'ticks' function.
|
||||
-- So we "rewind" it to the previous tick for the purpose of this display.
|
||||
renderDutyCycle :: GameState -> Robot -> Widget Name
|
||||
renderDutyCycle gs robot =
|
||||
withAttr dutyCycleAttr . str . flip (showFFloat (Just 1)) "%" $ dutyCyclePercentage
|
||||
where
|
||||
curTicks = gs ^. temporal . ticks
|
||||
window = robot ^. activityCounts . activityWindow
|
||||
|
||||
-- Rewind to previous tick
|
||||
latestRobotTick = addTicks (-1) curTicks
|
||||
dutyCycleRatio = WC.getOccupancy latestRobotTick window
|
||||
|
||||
dutyCycleAttr = safeIndex dutyCycleRatio meterAttributeNames
|
||||
|
||||
dutyCyclePercentage :: Double
|
||||
dutyCyclePercentage = 100 * getValue dutyCycleRatio
|
||||
|
||||
robotsListWidget :: AppState -> Widget Name
|
||||
robotsListWidget s = hCenter table
|
||||
where
|
||||
table =
|
||||
BT.renderTable
|
||||
. BT.columnBorders False
|
||||
. BT.setDefaultColAlignment BT.AlignCenter
|
||||
-- Inventory count is right aligned
|
||||
. BT.alignRight 4
|
||||
. BT.table
|
||||
$ map (padLeftRight 1) <$> (headers : robotsTable)
|
||||
headings =
|
||||
[ "Name"
|
||||
, "Age"
|
||||
, "Pos"
|
||||
, "Items"
|
||||
, "Status"
|
||||
, "Actns"
|
||||
, "Cmds"
|
||||
, "Cycles"
|
||||
, "Activity"
|
||||
, "Log"
|
||||
]
|
||||
headers = withAttr robotAttr . txt <$> applyWhen debugRID ("ID" :) headings
|
||||
robotsTable = mkRobotRow <$> robots
|
||||
mkRobotRow robot =
|
||||
applyWhen debugRID (idWidget :) cells
|
||||
where
|
||||
cells =
|
||||
[ nameWidget
|
||||
, str ageStr
|
||||
, locWidget
|
||||
, padRight (Pad 1) (str $ show rInvCount)
|
||||
, statusWidget
|
||||
, str $ show $ robot ^. activityCounts . tangibleCommandCount
|
||||
, -- TODO(#1341): May want to expose the details of this histogram in
|
||||
-- a per-robot pop-up
|
||||
str . show . sum . M.elems $ robot ^. activityCounts . commandsHistogram
|
||||
, str $ show $ robot ^. activityCounts . lifetimeStepCount
|
||||
, renderDutyCycle (s ^. gameState) robot
|
||||
, txt rLog
|
||||
]
|
||||
|
||||
idWidget = str $ show $ robot ^. robotID
|
||||
nameWidget =
|
||||
hBox
|
||||
[ renderDisplay (robot ^. robotDisplay)
|
||||
, highlightSystem . txt $ " " <> robot ^. robotName
|
||||
]
|
||||
|
||||
highlightSystem = if robot ^. systemRobot then withAttr highlightAttr else id
|
||||
|
||||
ageStr
|
||||
| age < 60 = show age <> "sec"
|
||||
| age < 3600 = show (age `div` 60) <> "min"
|
||||
| age < 3600 * 24 = show (age `div` 3600) <> "hour"
|
||||
| otherwise = show (age `div` 3600 * 24) <> "day"
|
||||
where
|
||||
TimeSpec createdAtSec _ = robot ^. robotCreatedAt
|
||||
TimeSpec nowSec _ = s ^. uiState . uiGameplay . uiTiming . lastFrameTime
|
||||
age = nowSec - createdAtSec
|
||||
|
||||
rInvCount = sum $ map fst . E.elems $ robot ^. robotEntity . entityInventory
|
||||
rLog
|
||||
| robot ^. robotLogUpdated = "x"
|
||||
| otherwise = " "
|
||||
|
||||
locWidget = hBox [worldCell, str $ " " <> locStr]
|
||||
where
|
||||
rCoords = fmap locToCoords rLoc
|
||||
rLoc = robot ^. robotLocation
|
||||
worldCell =
|
||||
drawLoc
|
||||
(s ^. uiState . uiGameplay)
|
||||
g
|
||||
rCoords
|
||||
locStr = renderCoordsString rLoc
|
||||
|
||||
statusWidget = case robot ^. machine of
|
||||
Waiting {} -> txt "waiting"
|
||||
_
|
||||
| isActive robot -> withAttr notifAttr $ txt "busy"
|
||||
| otherwise -> withAttr greenAttr $ txt "idle"
|
||||
|
||||
basePos :: Point V2 Double
|
||||
basePos = realToFrac <$> fromMaybe origin (g ^? baseRobot . robotLocation . planar)
|
||||
-- Keep the base and non system robot (e.g. no seed)
|
||||
isRelevant robot = robot ^. robotID == 0 || not (robot ^. systemRobot)
|
||||
-- Keep the robot that are less than 32 unit away from the base
|
||||
isNear robot = creative || distance (realToFrac <$> robot ^. robotLocation . planar) basePos < 32
|
||||
robots :: [Robot]
|
||||
robots =
|
||||
filter (\robot -> debugAllRobots || (isRelevant robot && isNear robot))
|
||||
. IM.elems
|
||||
$ g ^. robotInfo . robotMap
|
||||
creative = g ^. creativeMode
|
||||
debugRID = s ^. uiState . uiDebugOptions . Lens.contains ListRobotIDs
|
||||
debugAllRobots = s ^. uiState . uiDebugOptions . Lens.contains ListAllRobots
|
||||
g = s ^. gameState
|
@ -32,8 +32,8 @@ import Swarm.Game.Scenario.Topography.Structure.Recognition.Type
|
||||
import Swarm.Game.State
|
||||
import Swarm.Game.State.Substate (structureRecognition)
|
||||
import Swarm.Language.Syntax.Direction (directionJsonModifier)
|
||||
import Swarm.TUI.Model.Dialog.Structure
|
||||
import Swarm.TUI.Model.Name
|
||||
import Swarm.TUI.Model.Structure
|
||||
import Swarm.TUI.View.Attribute.Attr
|
||||
import Swarm.TUI.View.CellDisplay
|
||||
import Swarm.TUI.View.Util
|
||||
|
@ -25,6 +25,7 @@ import Swarm.Game.State
|
||||
import Swarm.Game.State.Landscape
|
||||
import Swarm.Game.State.Substate
|
||||
import Swarm.Game.Terrain
|
||||
import Swarm.Game.Universe
|
||||
import Swarm.Language.Pretty (prettyTextLine)
|
||||
import Swarm.Language.Syntax (Syntax)
|
||||
import Swarm.Language.Text.Markdown qualified as Markdown
|
||||
@ -255,3 +256,11 @@ bindingText s e = maybe "" ppBindingShort b
|
||||
Binding V.KLeft m | null m -> "←"
|
||||
Binding V.KRight m | null m -> "→"
|
||||
bi -> ppBinding bi
|
||||
|
||||
renderCoordsString :: Cosmic Location -> String
|
||||
renderCoordsString (Cosmic sw coords) =
|
||||
unwords $ locationToString coords : suffix
|
||||
where
|
||||
suffix = case sw of
|
||||
DefaultRootSubworld -> []
|
||||
SubworldName swName -> ["in", T.unpack swName]
|
||||
|
@ -78,7 +78,7 @@ import Swarm.Game.Step.Path.Type
|
||||
import Swarm.Language.Pipeline (processTermEither)
|
||||
import Swarm.Language.Pretty (prettyTextLine)
|
||||
import Swarm.TUI.Model hiding (SwarmKeyDispatchers (..))
|
||||
import Swarm.TUI.Model.Goal
|
||||
import Swarm.TUI.Model.Dialog.Goal
|
||||
import Swarm.TUI.Model.Repl (REPLHistItem, replHistory, replSeq)
|
||||
import Swarm.TUI.Model.UI
|
||||
import Swarm.Util.RingBuffer
|
||||
@ -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
|
||||
|
@ -1015,15 +1015,16 @@ library swarm-tui
|
||||
Swarm.TUI.Model
|
||||
Swarm.TUI.Model.Achievements
|
||||
Swarm.TUI.Model.DebugOption
|
||||
Swarm.TUI.Model.Dialog
|
||||
Swarm.TUI.Model.Dialog.Goal
|
||||
Swarm.TUI.Model.Dialog.Popup
|
||||
Swarm.TUI.Model.Dialog.Structure
|
||||
Swarm.TUI.Model.Event
|
||||
Swarm.TUI.Model.Goal
|
||||
Swarm.TUI.Model.KeyBindings
|
||||
Swarm.TUI.Model.Menu
|
||||
Swarm.TUI.Model.Name
|
||||
Swarm.TUI.Model.Popup
|
||||
Swarm.TUI.Model.Repl
|
||||
Swarm.TUI.Model.StateUpdate
|
||||
Swarm.TUI.Model.Structure
|
||||
Swarm.TUI.Model.UI
|
||||
Swarm.TUI.Model.WebCommand
|
||||
Swarm.TUI.Panel
|
||||
@ -1036,6 +1037,7 @@ library swarm-tui
|
||||
Swarm.TUI.View.Logo
|
||||
Swarm.TUI.View.Objective
|
||||
Swarm.TUI.View.Popup
|
||||
Swarm.TUI.View.Robot
|
||||
Swarm.TUI.View.Structure
|
||||
Swarm.TUI.View.Util
|
||||
|
||||
|
Loading…
Reference in New Issue
Block a user