From e98660b0e4c464a0a06c90a796c311f9e6b11a65 Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Ond=C5=99ej=20=C5=A0ebek?=
<44544735+xsebek@users.noreply.github.com>
Date: Mon, 29 Jul 2024 22:27:16 +0200
Subject: [PATCH] Add CLI option to start the game paused (#2080)
* add CLI option:
```
-p,--paused Pause the game at start.
```
* closes #2076
---
You can test it with:
```sh
cabal run swarm -O0 -- --scenario Tutorials/move --paused
```
After one step (Ctrl+O) the Goal dialog will show up along with the rest of the UI.
---
app/game/Main.hs | 36 +++++++++++--------
src/swarm-engine/Swarm/Game/State.hs | 3 +-
src/swarm-engine/Swarm/Game/State/Runtime.hs | 10 +++---
src/swarm-engine/Swarm/Game/State/Substate.hs | 6 ++--
src/swarm-scenario/Swarm/Game/State/Config.hs | 2 ++
.../Swarm/Web/Tournament/Validate.hs | 3 +-
src/swarm-tui/Swarm/TUI/Controller/Util.hs | 10 +++++-
src/swarm-tui/Swarm/TUI/Model.hs | 3 ++
src/swarm-tui/Swarm/TUI/Model/StateUpdate.hs | 4 +--
test/bench/Benchmark.hs | 2 +-
10 files changed, 52 insertions(+), 27 deletions(-)
diff --git a/app/game/Main.hs b/app/game/Main.hs
index bb7bd1c2..c59a16b1 100644
--- a/app/game/Main.hs
+++ b/app/game/Main.hs
@@ -1,10 +1,12 @@
+{-# LANGUAGE ApplicativeDo #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
+{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TemplateHaskell #-}
-- |
-- SPDX-License-Identifier: BSD-3-Clause
-module Main where
+module Main (main) where
import Control.Monad (when)
import Data.Foldable qualified
@@ -44,25 +46,29 @@ cliParser :: Parser CLI
cliParser =
subparser
( mconcat
- [ command "format" (info (Format <$> parseFormat) (progDesc "Format a file"))
+ [ command "run" (info (Run <$> appOpts <**> helper) (progDesc "Run the Swarm game (default)"))
+ , command "format" (info (Format <$> parseFormat) (progDesc "Format a file"))
, command "lsp" (info (pure LSP) (progDesc "Start the LSP"))
, command "version" (info (pure Version) (progDesc "Get current and upstream version."))
, command "keybindings" (info (ListKeybinding <$> initKeybindingConfig <*> printKeyMode <**> helper) (progDesc "List the keybindings"))
]
)
- <|> Run
- <$> ( AppOpts
- <$> seed
- <*> scenario
- <*> run
- <*> autoplay
- <*> speedFactor
- <*> cheat
- <*> color
- <*> webPort
- <*> pure gitInfo
- )
+ <|> Run <$> appOpts
where
+ appOpts :: Parser AppOpts
+ appOpts = do
+ let repoGitInfo = gitInfo
+ userSeed <- seed
+ userScenario <- scenario
+ scriptToRun <- run
+ pausedAtStart <- paused
+ autoPlay <- autoplay
+ speed <- speedFactor
+ cheatMode <- cheat
+ colorMode <- color
+ userWebPort <- webPort
+ return $ AppOpts {..}
+
input :: Parser FormatInput
input =
flag' Stdin (long "stdin" <> help "Read code from stdin")
@@ -108,6 +114,8 @@ cliParser =
scenario = optional $ strOption (long "scenario" <> short 'i' <> metavar "FILE" <> help "Name of an input scenario to load")
run :: Parser (Maybe String)
run = optional $ strOption (long "run" <> short 'r' <> metavar "FILE" <> help "Run the commands in a file at startup")
+ paused :: Parser Bool
+ paused = switch (long "paused" <> short 'p' <> help "Pause the game at start.")
autoplay :: Parser Bool
autoplay = switch (long "autoplay" <> short 'a' <> help "Automatically run the solution defined in the scenario, if there is one. Mutually exclusive with --run.")
speedFactor :: Parser Int
diff --git a/src/swarm-engine/Swarm/Game/State.hs b/src/swarm-engine/Swarm/Game/State.hs
index cba84bdd..c97d842a 100644
--- a/src/swarm-engine/Swarm/Game/State.hs
+++ b/src/swarm-engine/Swarm/Game/State.hs
@@ -103,6 +103,7 @@ import Swarm.Game.Location
import Swarm.Game.Robot
import Swarm.Game.Robot.Concrete
import Swarm.Game.Scenario.Status
+import Swarm.Game.State.Config
import Swarm.Game.State.Landscape
import Swarm.Game.State.Robot
import Swarm.Game.State.Substate
@@ -457,7 +458,7 @@ initGameState :: GameStateConfig -> GameState
initGameState gsc =
GameState
{ _creativeMode = False
- , _temporal = initTemporalState
+ , _temporal = initTemporalState $ startPaused gsc
, _winCondition = NoWinCondition
, _winSolution = Nothing
, _robotInfo = initRobots gsc
diff --git a/src/swarm-engine/Swarm/Game/State/Runtime.hs b/src/swarm-engine/Swarm/Game/State/Runtime.hs
index 97c943d8..d76d151a 100644
--- a/src/swarm-engine/Swarm/Game/State/Runtime.hs
+++ b/src/swarm-engine/Swarm/Game/State/Runtime.hs
@@ -78,21 +78,23 @@ initGameStateConfig ::
, Has (Accum (Seq SystemFailure)) sig m
, Has (Lift IO) sig m
) =>
+ Bool ->
m GameStateConfig
-initGameStateConfig = do
+initGameStateConfig pause = do
gsi <- initGameStateInputs
appDataMap <- readAppData
nameGen <- initNameGenerator appDataMap
- return $ GameStateConfig appDataMap nameGen gsi
+ return $ GameStateConfig appDataMap nameGen pause gsi
initRuntimeState ::
( Has (Throw SystemFailure) sig m
, Has (Accum (Seq SystemFailure)) sig m
, Has (Lift IO) sig m
) =>
+ Bool ->
m RuntimeState
-initRuntimeState = do
- gsc <- initGameStateConfig
+initRuntimeState pause = do
+ gsc <- initGameStateConfig pause
scenarios <- loadScenarios $ gsiScenarioInputs $ initState gsc
return $
diff --git a/src/swarm-engine/Swarm/Game/State/Substate.hs b/src/swarm-engine/Swarm/Game/State/Substate.hs
index 52231664..6374cb43 100644
--- a/src/swarm-engine/Swarm/Game/State/Substate.hs
+++ b/src/swarm-engine/Swarm/Game/State/Substate.hs
@@ -392,11 +392,11 @@ defaultRobotStepsPerTick = 100
-- * Record initialization
-initTemporalState :: TemporalState
-initTemporalState =
+initTemporalState :: Bool -> TemporalState
+initTemporalState pausedAtStart =
TemporalState
{ _gameStep = WorldTick
- , _runStatus = Running
+ , _runStatus = if pausedAtStart then ManualPause else Running
, _ticks = TickNumber 0
, _robotStepsPerTick = defaultRobotStepsPerTick
}
diff --git a/src/swarm-scenario/Swarm/Game/State/Config.hs b/src/swarm-scenario/Swarm/Game/State/Config.hs
index 7ad9b79f..03978f64 100644
--- a/src/swarm-scenario/Swarm/Game/State/Config.hs
+++ b/src/swarm-scenario/Swarm/Game/State/Config.hs
@@ -16,5 +16,7 @@ data GameStateConfig = GameStateConfig
{ initAppDataMap :: Map Text Text
, nameParts :: NameGenerator
-- ^ Lists of words/adjectives for use in building random robot names.
+ , startPaused :: Bool
+ -- ^ Start the game paused - useful for debugging or competitive play.
, initState :: GameStateInputs
}
diff --git a/src/swarm-tournament/Swarm/Web/Tournament/Validate.hs b/src/swarm-tournament/Swarm/Web/Tournament/Validate.hs
index 997a56df..e8913a4d 100644
--- a/src/swarm-tournament/Swarm/Web/Tournament/Validate.hs
+++ b/src/swarm-tournament/Swarm/Web/Tournament/Validate.hs
@@ -183,7 +183,8 @@ gamestateFromScenarioText content = do
withExceptT (ScenarioEnvironmentFailure . ContextInitializationFailure)
. ExceptT
. runThrow
- $ evalAccum (mempty :: Seq SystemFailure) initGameStateConfig
+ . evalAccum (mempty :: Seq SystemFailure)
+ $ initGameStateConfig False
let scenarioInputs = gsiScenarioInputs $ initState gsc
scenarioObject <- initScenarioObject scenarioInputs content
diff --git a/src/swarm-tui/Swarm/TUI/Controller/Util.hs b/src/swarm-tui/Swarm/TUI/Controller/Util.hs
index 9d329cca..20713716 100644
--- a/src/swarm-tui/Swarm/TUI/Controller/Util.hs
+++ b/src/swarm-tui/Swarm/TUI/Controller/Util.hs
@@ -33,7 +33,15 @@ import Swarm.Game.World qualified as W
import Swarm.Game.World.Coords
import Swarm.Language.Capability (Capability (CDebug))
import Swarm.Language.Syntax hiding (Key)
-import Swarm.TUI.Model
+import Swarm.TUI.Model (
+ AppState,
+ FocusablePanel,
+ ModalType (..),
+ Name (..),
+ gameState,
+ modalScroll,
+ uiState,
+ )
import Swarm.TUI.Model.Repl (REPLHistItem, REPLPrompt, REPLState, addREPLItem, replHistory, replPromptText, replPromptType)
import Swarm.TUI.Model.UI
import Swarm.TUI.View.Util (generateModal)
diff --git a/src/swarm-tui/Swarm/TUI/Model.hs b/src/swarm-tui/Swarm/TUI/Model.hs
index 0eebb453..2f8930b1 100644
--- a/src/swarm-tui/Swarm/TUI/Model.hs
+++ b/src/swarm-tui/Swarm/TUI/Model.hs
@@ -249,6 +249,8 @@ data AppOpts = AppOpts
-- ^ Scenario the user wants to play.
, scriptToRun :: Maybe FilePath
-- ^ Code to be run on base.
+ , pausedAtStart :: Bool
+ -- ^ Pause the game on start by default.
, autoPlay :: Bool
-- ^ Automatically run the solution defined in the scenario file
, speed :: Int
@@ -270,6 +272,7 @@ defaultAppOpts =
{ userSeed = Nothing
, userScenario = Nothing
, scriptToRun = Nothing
+ , pausedAtStart = False
, autoPlay = False
, speed = defaultInitLgTicksPerSecond
, cheatMode = False
diff --git a/src/swarm-tui/Swarm/TUI/Model/StateUpdate.hs b/src/swarm-tui/Swarm/TUI/Model/StateUpdate.hs
index 71d0f2a3..058db443 100644
--- a/src/swarm-tui/Swarm/TUI/Model/StateUpdate.hs
+++ b/src/swarm-tui/Swarm/TUI/Model/StateUpdate.hs
@@ -125,7 +125,7 @@ initPersistentState ::
m (RuntimeState, UIState, KeyEventHandlingState)
initPersistentState opts@(AppOpts {..}) = do
(warnings :: Seq SystemFailure, (initRS, initUI, initKs)) <- runAccum mempty $ do
- rs <- initRuntimeState
+ rs <- initRuntimeState pausedAtStart
ui <- initUIState speed (not (skipMenu opts)) cheatMode
ks <- initKeyHandlingState
return (rs, ui, ks)
@@ -142,7 +142,7 @@ constructAppState ::
AppOpts ->
m AppState
constructAppState rs ui key opts@(AppOpts {..}) = do
- let gs = initGameState $ rs ^. stdGameConfigInputs
+ let gs = initGameState (rs ^. stdGameConfigInputs)
case skipMenu opts of
False -> return $ AppState gs (ui & uiGameplay . uiTiming . lgTicksPerSecond .~ defaultInitLgTicksPerSecond) key rs
True -> do
diff --git a/test/bench/Benchmark.hs b/test/bench/Benchmark.hs
index 71b42fdf..a5d44bad 100644
--- a/test/bench/Benchmark.hs
+++ b/test/bench/Benchmark.hs
@@ -142,7 +142,7 @@ mkGameState prog robotMaker numRobots = do
-- NOTE: This replaces "classicGame0", which is still used by unit tests.
gs <- simpleErrorHandle $ do
- (_ :: Seq SystemFailure, initRS) <- runAccum mempty initRuntimeState
+ (_ :: Seq SystemFailure, initRS) <- runAccum mempty $ initRuntimeState False
(scenario, _) <- loadStandaloneScenario "classic"
return $ pureScenarioToGameState scenario 0 0 Nothing $ view stdGameConfigInputs initRS