Restyled by fourmolu (#2097)

Co-authored-by: Restyled.io <commits@restyled.io>
This commit is contained in:
restyled-io[bot] 2024-08-04 23:08:22 +02:00 committed by GitHub
parent e5c1f04443
commit bc6e8049ae
No known key found for this signature in database
GPG Key ID: B5690EEEBB952194
4 changed files with 17 additions and 13 deletions

View File

@ -458,8 +458,9 @@ initGameState :: GameStateConfig -> GameState
initGameState gsc =
GameState
{ _creativeMode = False
, _temporal = initTemporalState (startPaused gsc)
& pauseOnCompletion .~ (if pauseOnObjectiveCompletion gsc then PauseOnAnyObjective else PauseOnWin)
, _temporal =
initTemporalState (startPaused gsc)
& pauseOnCompletion .~ (if pauseOnObjectiveCompletion gsc then PauseOnAnyObjective else PauseOnWin)
, _winCondition = NoWinCondition
, _winSolution = Nothing
, _robotInfo = initRobots gsc

View File

@ -1,5 +1,5 @@
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TemplateHaskell #-}
-- |
-- SPDX-License-Identifier: BSD-3-Clause

View File

@ -27,7 +27,7 @@ module Swarm.Game.State.Substate (
-- *** Temporal state
TemporalState,
PauseOnObjective(..),
PauseOnObjective (..),
initTemporalState,
gameStep,
runStatus,

View File

@ -28,9 +28,11 @@ import Control.Effect.Lens
import Control.Effect.Lift
import Control.Lens as Lens hiding (Const, distrib, from, parts, use, uses, view, (%=), (+=), (.=), (<+=), (<>=))
import Control.Monad (foldM, forM_, unless, when)
import Data.Foldable.Extra (notNull)
import Data.Functor (void)
import Data.IntMap qualified as IM
import Data.IntSet qualified as IS
import Data.List (intercalate)
import Data.Map qualified as M
import Data.Maybe (fromMaybe)
import Data.Sequence ((><))
@ -75,8 +77,6 @@ import Swarm.Util.WindowedCounter qualified as WC
import System.Clock (TimeSpec)
import Witch (From (from))
import Prelude hiding (Applicative (..), lookup)
import Data.Foldable.Extra (notNull)
import Data.List (intercalate)
-- | The main function to do one game tick.
--
@ -341,15 +341,18 @@ hypotheticalWinCheck em g ws oc = do
_ -> return ()
queue <- messageInfo . announcementQueue Swarm.Util.<%= (>< Seq.fromList (map ObjectiveCompleted $ completionAnnouncementQueue finalAccumulator))
shouldPause <- use $ temporal . pauseOnCompletion
-- 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"
]
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"
]
when (newWinState /= Ongoing || (notNull queue && shouldPause == PauseOnAnyObjective)) $
temporal . runStatus .= AutoPause