Skip to content

Commit

Permalink
Renaming and fixups
Browse files Browse the repository at this point in the history
  • Loading branch information
xsebek committed Sep 8, 2024
1 parent 5cc73f4 commit 10c0af1
Show file tree
Hide file tree
Showing 6 changed files with 33 additions and 23 deletions.
2 changes: 1 addition & 1 deletion app/game/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -67,7 +67,7 @@ cliParser =
scriptToRun <- run
pausedAtStart <- paused
autoPlay <- autoplay
showGoal <- not <$> hideGoal
autoShowObjectives <- not <$> hideGoal
speed <- speedFactor
debugOptions <- debug
cheatMode <- cheat
Expand Down
10 changes: 6 additions & 4 deletions src/swarm-engine/Swarm/Game/Step.hs
Original file line number Diff line number Diff line change
Expand Up @@ -343,18 +343,20 @@ hypotheticalWinCheck em g ws oc = do
queue <- messageInfo . announcementQueue Swarm.Util.<%= (>< Seq.fromList (map ObjectiveCompleted $ completionAnnouncementQueue finalAccumulator))

shouldPause <- use $ temporal . pauseOnCompletion
let willPause = newWinState /= Ongoing || (notNull queue && shouldPause == PauseOnAnyObjective)
-- TODO: remove this debug ouput
sendIO $
appendFile "log_win.txt" $
intercalate
" \t"
[ show $ getTickNumber ts
, if newWinState == Ongoing then "ongoing" else "won"
, if (notNull queue) then "queued" else "empty"
, show shouldPause <> "\n"
]
, if notNull queue then "queued" else "empty"
, show shouldPause
, if willPause then "AutoPause" else "Running"
] <> "\n"

when (newWinState /= Ongoing || (notNull queue && shouldPause == PauseOnAnyObjective)) $
when willPause $
temporal . runStatus .= AutoPause

mapM_ handleException $ exceptions finalAccumulator
Expand Down
4 changes: 2 additions & 2 deletions src/swarm-tui/Swarm/TUI/Controller/UpdateUI.hs
Original file line number Diff line number Diff line change
Expand Up @@ -237,8 +237,8 @@ doGoalUpdates = do
-- automatically popped up.
gameState . messageInfo . announcementQueue .= mempty

hideObjectives <- use $ uiState . uiGameplay . uiHideObjectives
unless hideObjectives $ openModal GoalModal
showObjectives <- use $ uiState . uiGameplay . uiAutoShowObjectives
when showObjectives $ openModal GoalModal

return goalWasUpdated
where
Expand Down
6 changes: 3 additions & 3 deletions src/swarm-tui/Swarm/TUI/Model.hs
Original file line number Diff line number Diff line change
Expand Up @@ -255,8 +255,8 @@ data AppOpts = AppOpts
-- ^ Pause the game on start by default.
, autoPlay :: Bool
-- ^ Automatically run the solution defined in the scenario file
, showGoal :: Bool
-- ^ Show goal dialogs.
, autoShowObjectives :: Bool
-- ^ Show objectives dialogs when an objective is achieved/failed.
, speed :: Int
-- ^ Initial game speed (logarithm)
, debugOptions :: Set DebugOption
Expand All @@ -277,7 +277,7 @@ defaultAppOpts =
, userScenario = Nothing
, scriptToRun = Nothing
, pausedAtStart = False
, showGoal = True
, autoShowObjectives = True
, autoPlay = False
, speed = defaultInitLgTicksPerSecond
, debugOptions = mempty
Expand Down
6 changes: 4 additions & 2 deletions src/swarm-tui/Swarm/TUI/Model/StateUpdate.hs
Original file line number Diff line number Diff line change
Expand Up @@ -131,10 +131,12 @@ initPersistentState opts@(AppOpts {..}) = do
initRuntimeState
RuntimeOptions
{ startPaused = pausedAtStart
, pauseOnObjectiveCompletion = showGoal
, pauseOnObjectiveCompletion = autoShowObjectives
, loadTestScenarios = Set.member LoadTestingScenarios debugOptions
}
ui <- initUIState speed (not (skipMenu opts)) debugOptions
let showMainMenu = not (skipMenu opts)
ui <- initUIState UIInitOptions {..}
-- \$ speed (not (skipMenu opts)) debugOptions
ks <- initKeyHandlingState
return (rs, ui, ks)
let initRS' = addWarnings initRS (F.toList warnings)
Expand Down
28 changes: 17 additions & 11 deletions src/swarm-tui/Swarm/TUI/Model/UI.hs
Original file line number Diff line number Diff line change
Expand Up @@ -32,7 +32,7 @@ module Swarm.TUI.Model.UI (
uiGoal,
uiStructure,
uiIsAutoPlay,
uiHideObjectives,
uiAutoShowObjectives,
uiAchievements,
lgTicksPerSecond,
lastFrameTime,
Expand All @@ -57,6 +57,7 @@ module Swarm.TUI.Model.UI (
initFocusRing,
defaultInitLgTicksPerSecond,
initUIState,
UIInitOptions (..),
) where

import Brick (AttrMap)
Expand Down Expand Up @@ -208,7 +209,7 @@ data UIGameplay = UIGameplay
, _uiGoal :: GoalDisplay
, _uiStructure :: StructureDisplay
, _uiIsAutoPlay :: Bool
, _uiHideObjectives :: Bool
, _uiAutoShowObjectives :: Bool
, _uiShowREPL :: Bool
, _uiShowDebug :: Bool
, _uiHideRobotsUntil :: TimeSpec
Expand Down Expand Up @@ -258,7 +259,7 @@ uiStructure :: Lens' UIGameplay StructureDisplay
uiIsAutoPlay :: Lens' UIGameplay Bool

-- | Do not open objectives modals on objective completion.
uiHideObjectives :: Lens' UIGameplay Bool
uiAutoShowObjectives :: Lens' UIGameplay Bool

-- | A toggle to expand or collapse the REPL by pressing @Ctrl-k@
uiShowREPL :: Lens' UIGameplay Bool
Expand Down Expand Up @@ -339,6 +340,14 @@ initFocusRing = focusRing $ map FocusablePanel enumerate
defaultInitLgTicksPerSecond :: Int
defaultInitLgTicksPerSecond = 4 -- 2^4 = 16 ticks / second

data UIInitOptions = UIInitOptions
{ speed :: Int
, showMainMenu :: Bool
, autoShowObjectives :: Bool
, debugOptions :: Set DebugOption
}
deriving (Eq, Show)

-- | Initialize the UI state. This needs to be in the IO monad since
-- it involves reading a REPL history file, getting the current
-- time, and loading text files from the data directory. The @Bool@
Expand All @@ -348,12 +357,9 @@ initUIState ::
( Has (Accum (Seq SystemFailure)) sig m
, Has (Lift IO) sig m
) =>
Int ->
Bool ->
Set DebugOption ->
UIInitOptions ->
m UIState
initUIState speedFactor showMainMenu debug = do
-- TODO: ondra - add ui config for silence
initUIState UIInitOptions {..} = do
historyT <- sendIO $ readFileMayT =<< getSwarmHistoryPath False
let history = maybe [] (map mkREPLSubmission . T.lines) historyT
startTime <- sendIO $ getTime Monotonic
Expand All @@ -363,7 +369,7 @@ initUIState speedFactor showMainMenu debug = do
UIState
{ _uiMenu = if showMainMenu then MainMenu (mainMenu NewGame) else NoMenu
, _uiPlaying = not showMainMenu
, _uiDebugOptions = debug
, _uiDebugOptions = debugOptions
, _uiLaunchConfig = launchConfigPanel
, _uiAchievements = M.fromList $ map (view achievement &&& id) achievements
, _uiAttrMap = swarmAttrMap
Expand All @@ -387,13 +393,13 @@ initUIState speedFactor showMainMenu debug = do
, _uiGoal = emptyGoalDisplay
, _uiStructure = emptyStructureDisplay
, _uiIsAutoPlay = False
, _uiHideObjectives = True
, _uiAutoShowObjectives = autoShowObjectives
, _uiTiming =
UITiming
{ _uiShowFPS = False
, _uiTPF = 0
, _uiFPS = 0
, _lgTicksPerSecond = speedFactor
, _lgTicksPerSecond = speed
, _lastFrameTime = startTime
, _accumulatedTime = 0
, _lastInfoTime = 0
Expand Down

0 comments on commit 10c0af1

Please sign in to comment.