Skip to content

Commit

Permalink
Restyled by fourmolu (#2097)
Browse files Browse the repository at this point in the history
Co-authored-by: Restyled.io <[email protected]>
  • Loading branch information
restyled-io[bot] and restyled-commits authored Aug 4, 2024
1 parent e5c1f04 commit bc6e804
Show file tree
Hide file tree
Showing 4 changed files with 17 additions and 13 deletions.
5 changes: 3 additions & 2 deletions src/swarm-engine/Swarm/Game/State.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down
2 changes: 1 addition & 1 deletion src/swarm-engine/Swarm/Game/State/Runtime.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,5 @@
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TemplateHaskell #-}

-- |
-- SPDX-License-Identifier: BSD-3-Clause
Expand Down
2 changes: 1 addition & 1 deletion src/swarm-engine/Swarm/Game/State/Substate.hs
Original file line number Diff line number Diff line change
Expand Up @@ -27,7 +27,7 @@ module Swarm.Game.State.Substate (

-- *** Temporal state
TemporalState,
PauseOnObjective(..),
PauseOnObjective (..),
initTemporalState,
gameStep,
runStatus,
Expand Down
21 changes: 12 additions & 9 deletions src/swarm-engine/Swarm/Game/Step.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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 ((><))
Expand Down Expand Up @@ -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.
--
Expand Down Expand Up @@ -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"

Check warning on line 353 in src/swarm-engine/Swarm/Game/Step.hs

View workflow job for this annotation

GitHub Actions / HLint

Suggestion in hypotheticalWinCheck in module Swarm.Game.Step: Redundant bracket ▫︎ Found: "if (notNull queue) then \"queued\" else \"empty\"" ▫︎ Perhaps: "if notNull queue then \"queued\" else \"empty\""
, show shouldPause <> "\n"
]

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

0 comments on commit bc6e804

Please sign in to comment.