module Swarm.TUI.Controller.SaveScenario (
saveScenarioInfoOnFinish,
saveScenarioInfoOnFinishNocheat,
saveScenarioInfoOnQuit,
) where
import Brick.Widgets.List qualified as BL
import Control.Lens as Lens
import Control.Monad (forM_, unless, void, when)
import Control.Monad.IO.Class (MonadIO (liftIO))
import Control.Monad.State (MonadState)
import Data.Maybe (fromMaybe)
import Data.Time (getZonedTime)
import Swarm.Game.Achievement.Definitions
import Swarm.Game.Scenario.Status (updateScenarioInfoOnFinish)
import Swarm.Game.ScenarioInfo
import Swarm.Game.State
import Swarm.Game.State.Runtime
import Swarm.Game.State.Substate
import Swarm.TUI.Model
import Swarm.TUI.Model.Achievements (attainAchievement')
import Swarm.TUI.Model.Repl
import Swarm.TUI.Model.UI
import System.FilePath (splitDirectories)
import Prelude hiding (Applicative (..))
getNormalizedCurrentScenarioPath :: (MonadIO m, MonadState AppState m) => m (Maybe FilePath)
getNormalizedCurrentScenarioPath :: forall (m :: * -> *).
(MonadIO m, MonadState AppState m) =>
m (Maybe FilePath)
getNormalizedCurrentScenarioPath =
Getting (Maybe FilePath) AppState (Maybe FilePath)
-> m (Maybe FilePath)
forall s (m :: * -> *) a. MonadState s m => Getting a s a -> m a
use ((GameState -> Const (Maybe FilePath) GameState)
-> AppState -> Const (Maybe FilePath) AppState
Lens' AppState GameState
gameState ((GameState -> Const (Maybe FilePath) GameState)
-> AppState -> Const (Maybe FilePath) AppState)
-> ((Maybe FilePath -> Const (Maybe FilePath) (Maybe FilePath))
-> GameState -> Const (Maybe FilePath) GameState)
-> Getting (Maybe FilePath) AppState (Maybe FilePath)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Maybe FilePath -> Const (Maybe FilePath) (Maybe FilePath))
-> GameState -> Const (Maybe FilePath) GameState
Lens' GameState (Maybe FilePath)
currentScenarioPath) m (Maybe FilePath)
-> (Maybe FilePath -> m (Maybe FilePath)) -> m (Maybe FilePath)
forall a b. m a -> (a -> m b) -> m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Maybe FilePath
Nothing -> Maybe FilePath -> m (Maybe FilePath)
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe FilePath
forall a. Maybe a
Nothing
Just FilePath
p' -> do
ScenarioCollection
gs <- Getting ScenarioCollection AppState ScenarioCollection
-> m ScenarioCollection
forall s (m :: * -> *) a. MonadState s m => Getting a s a -> m a
use (Getting ScenarioCollection AppState ScenarioCollection
-> m ScenarioCollection)
-> Getting ScenarioCollection AppState ScenarioCollection
-> m ScenarioCollection
forall a b. (a -> b) -> a -> b
$ (RuntimeState -> Const ScenarioCollection RuntimeState)
-> AppState -> Const ScenarioCollection AppState
Lens' AppState RuntimeState
runtimeState ((RuntimeState -> Const ScenarioCollection RuntimeState)
-> AppState -> Const ScenarioCollection AppState)
-> ((ScenarioCollection
-> Const ScenarioCollection ScenarioCollection)
-> RuntimeState -> Const ScenarioCollection RuntimeState)
-> Getting ScenarioCollection AppState ScenarioCollection
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ScenarioCollection -> Const ScenarioCollection ScenarioCollection)
-> RuntimeState -> Const ScenarioCollection RuntimeState
Lens' RuntimeState ScenarioCollection
scenarios
FilePath -> Maybe FilePath
forall a. a -> Maybe a
Just (FilePath -> Maybe FilePath) -> m FilePath -> m (Maybe FilePath)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO FilePath -> m FilePath
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (ScenarioCollection -> FilePath -> IO FilePath
forall (m :: * -> *).
MonadIO m =>
ScenarioCollection -> FilePath -> m FilePath
normalizeScenarioPath ScenarioCollection
gs FilePath
p')
saveScenarioInfoOnFinish :: (MonadIO m, MonadState AppState m) => FilePath -> m (Maybe ScenarioInfo)
saveScenarioInfoOnFinish :: forall (m :: * -> *).
(MonadIO m, MonadState AppState m) =>
FilePath -> m (Maybe ScenarioInfo)
saveScenarioInfoOnFinish FilePath
p = do
Maybe TSyntax
initialRunCode <- Getting (Maybe TSyntax) AppState (Maybe TSyntax)
-> m (Maybe TSyntax)
forall s (m :: * -> *) a. MonadState s m => Getting a s a -> m a
use (Getting (Maybe TSyntax) AppState (Maybe TSyntax)
-> m (Maybe TSyntax))
-> Getting (Maybe TSyntax) AppState (Maybe TSyntax)
-> m (Maybe TSyntax)
forall a b. (a -> b) -> a -> b
$ (GameState -> Const (Maybe TSyntax) GameState)
-> AppState -> Const (Maybe TSyntax) AppState
Lens' AppState GameState
gameState ((GameState -> Const (Maybe TSyntax) GameState)
-> AppState -> Const (Maybe TSyntax) AppState)
-> ((Maybe TSyntax -> Const (Maybe TSyntax) (Maybe TSyntax))
-> GameState -> Const (Maybe TSyntax) GameState)
-> Getting (Maybe TSyntax) AppState (Maybe TSyntax)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (GameControls -> Const (Maybe TSyntax) GameControls)
-> GameState -> Const (Maybe TSyntax) GameState
Lens' GameState GameControls
gameControls ((GameControls -> Const (Maybe TSyntax) GameControls)
-> GameState -> Const (Maybe TSyntax) GameState)
-> ((Maybe TSyntax -> Const (Maybe TSyntax) (Maybe TSyntax))
-> GameControls -> Const (Maybe TSyntax) GameControls)
-> (Maybe TSyntax -> Const (Maybe TSyntax) (Maybe TSyntax))
-> GameState
-> Const (Maybe TSyntax) GameState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Maybe TSyntax -> Const (Maybe TSyntax) (Maybe TSyntax))
-> GameControls -> Const (Maybe TSyntax) GameControls
Lens' GameControls (Maybe TSyntax)
initiallyRunCode
ZonedTime
t <- IO ZonedTime -> m ZonedTime
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO ZonedTime
getZonedTime
WinCondition
wc <- Getting WinCondition AppState WinCondition -> m WinCondition
forall s (m :: * -> *) a. MonadState s m => Getting a s a -> m a
use (Getting WinCondition AppState WinCondition -> m WinCondition)
-> Getting WinCondition AppState WinCondition -> m WinCondition
forall a b. (a -> b) -> a -> b
$ (GameState -> Const WinCondition GameState)
-> AppState -> Const WinCondition AppState
Lens' AppState GameState
gameState ((GameState -> Const WinCondition GameState)
-> AppState -> Const WinCondition AppState)
-> ((WinCondition -> Const WinCondition WinCondition)
-> GameState -> Const WinCondition GameState)
-> Getting WinCondition AppState WinCondition
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (WinCondition -> Const WinCondition WinCondition)
-> GameState -> Const WinCondition GameState
Lens' GameState WinCondition
winCondition
let won :: Bool
won = case WinCondition
wc of
WinConditions (Won Bool
_ TickNumber
_) ObjectiveCompletion
_ -> Bool
True
WinCondition
_ -> Bool
False
TickNumber
ts <- Getting TickNumber AppState TickNumber -> m TickNumber
forall s (m :: * -> *) a. MonadState s m => Getting a s a -> m a
use (Getting TickNumber AppState TickNumber -> m TickNumber)
-> Getting TickNumber AppState TickNumber -> m TickNumber
forall a b. (a -> b) -> a -> b
$ (GameState -> Const TickNumber GameState)
-> AppState -> Const TickNumber AppState
Lens' AppState GameState
gameState ((GameState -> Const TickNumber GameState)
-> AppState -> Const TickNumber AppState)
-> ((TickNumber -> Const TickNumber TickNumber)
-> GameState -> Const TickNumber GameState)
-> Getting TickNumber AppState TickNumber
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (TemporalState -> Const TickNumber TemporalState)
-> GameState -> Const TickNumber GameState
Lens' GameState TemporalState
temporal ((TemporalState -> Const TickNumber TemporalState)
-> GameState -> Const TickNumber GameState)
-> ((TickNumber -> Const TickNumber TickNumber)
-> TemporalState -> Const TickNumber TemporalState)
-> (TickNumber -> Const TickNumber TickNumber)
-> GameState
-> Const TickNumber GameState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (TickNumber -> Const TickNumber TickNumber)
-> TemporalState -> Const TickNumber TemporalState
Lens' TemporalState TickNumber
ticks
let currentScenarioInfo :: Traversal' AppState ScenarioInfo
currentScenarioInfo :: Traversal' AppState ScenarioInfo
currentScenarioInfo = (RuntimeState -> f RuntimeState) -> AppState -> f AppState
Lens' AppState RuntimeState
runtimeState ((RuntimeState -> f RuntimeState) -> AppState -> f AppState)
-> ((ScenarioInfo -> f ScenarioInfo)
-> RuntimeState -> f RuntimeState)
-> (ScenarioInfo -> f ScenarioInfo)
-> AppState
-> f AppState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ScenarioCollection -> f ScenarioCollection)
-> RuntimeState -> f RuntimeState
Lens' RuntimeState ScenarioCollection
scenarios ((ScenarioCollection -> f ScenarioCollection)
-> RuntimeState -> f RuntimeState)
-> ((ScenarioInfo -> f ScenarioInfo)
-> ScenarioCollection -> f ScenarioCollection)
-> (ScenarioInfo -> f ScenarioInfo)
-> RuntimeState
-> f RuntimeState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> Traversal' ScenarioCollection ScenarioItem
scenarioItemByPath FilePath
p ((ScenarioItem -> f ScenarioItem)
-> ScenarioCollection -> f ScenarioCollection)
-> ((ScenarioInfo -> f ScenarioInfo)
-> ScenarioItem -> f ScenarioItem)
-> (ScenarioInfo -> f ScenarioInfo)
-> ScenarioCollection
-> f ScenarioCollection
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ScenarioInfoPair -> f ScenarioInfoPair)
-> ScenarioItem -> f ScenarioItem
Prism' ScenarioItem ScenarioInfoPair
_SISingle ((ScenarioInfoPair -> f ScenarioInfoPair)
-> ScenarioItem -> f ScenarioItem)
-> ((ScenarioInfo -> f ScenarioInfo)
-> ScenarioInfoPair -> f ScenarioInfoPair)
-> (ScenarioInfo -> f ScenarioInfo)
-> ScenarioItem
-> f ScenarioItem
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ScenarioInfo -> f ScenarioInfo)
-> ScenarioInfoPair -> f ScenarioInfoPair
forall s t a b. Field2 s t a b => Lens s t a b
Lens ScenarioInfoPair ScenarioInfoPair ScenarioInfo ScenarioInfo
_2
REPLHistory
replHist <- Getting REPLHistory AppState REPLHistory -> m REPLHistory
forall s (m :: * -> *) a. MonadState s m => Getting a s a -> m a
use (Getting REPLHistory AppState REPLHistory -> m REPLHistory)
-> Getting REPLHistory AppState REPLHistory -> m REPLHistory
forall a b. (a -> b) -> a -> b
$ (UIState -> Const REPLHistory UIState)
-> AppState -> Const REPLHistory AppState
Lens' AppState UIState
uiState ((UIState -> Const REPLHistory UIState)
-> AppState -> Const REPLHistory AppState)
-> ((REPLHistory -> Const REPLHistory REPLHistory)
-> UIState -> Const REPLHistory UIState)
-> Getting REPLHistory AppState REPLHistory
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (UIGameplay -> Const REPLHistory UIGameplay)
-> UIState -> Const REPLHistory UIState
Lens' UIState UIGameplay
uiGameplay ((UIGameplay -> Const REPLHistory UIGameplay)
-> UIState -> Const REPLHistory UIState)
-> ((REPLHistory -> Const REPLHistory REPLHistory)
-> UIGameplay -> Const REPLHistory UIGameplay)
-> (REPLHistory -> Const REPLHistory REPLHistory)
-> UIState
-> Const REPLHistory UIState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (REPLState -> Const REPLHistory REPLState)
-> UIGameplay -> Const REPLHistory UIGameplay
Lens' UIGameplay REPLState
uiREPL ((REPLState -> Const REPLHistory REPLState)
-> UIGameplay -> Const REPLHistory UIGameplay)
-> ((REPLHistory -> Const REPLHistory REPLHistory)
-> REPLState -> Const REPLHistory REPLState)
-> (REPLHistory -> Const REPLHistory REPLHistory)
-> UIGameplay
-> Const REPLHistory UIGameplay
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (REPLHistory -> Const REPLHistory REPLHistory)
-> REPLState -> Const REPLHistory REPLState
Lens' REPLState REPLHistory
replHistory
let determinator :: CodeSizeDeterminators
determinator = Maybe TSyntax -> Bool -> CodeSizeDeterminators
CodeSizeDeterminators Maybe TSyntax
initialRunCode (Bool -> CodeSizeDeterminators) -> Bool -> CodeSizeDeterminators
forall a b. (a -> b) -> a -> b
$ REPLHistory
replHist REPLHistory -> Getting Bool REPLHistory Bool -> Bool
forall s a. s -> Getting a s a -> a
^. Getting Bool REPLHistory Bool
Lens' REPLHistory Bool
replHasExecutedManualInput
(ScenarioInfo -> Identity ScenarioInfo)
-> AppState -> Identity AppState
Traversal' AppState ScenarioInfo
currentScenarioInfo
((ScenarioInfo -> Identity ScenarioInfo)
-> AppState -> Identity AppState)
-> (ScenarioInfo -> ScenarioInfo) -> m ()
forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> (a -> b) -> m ()
%= CodeSizeDeterminators
-> ZonedTime -> TickNumber -> Bool -> ScenarioInfo -> ScenarioInfo
updateScenarioInfoOnFinish CodeSizeDeterminators
determinator ZonedTime
t TickNumber
ts Bool
won
Maybe ScenarioInfo
status <- Getting (First ScenarioInfo) AppState ScenarioInfo
-> m (Maybe ScenarioInfo)
forall s (m :: * -> *) a.
MonadState s m =>
Getting (First a) s a -> m (Maybe a)
preuse Getting (First ScenarioInfo) AppState ScenarioInfo
Traversal' AppState ScenarioInfo
currentScenarioInfo
case Maybe ScenarioInfo
status of
Maybe ScenarioInfo
Nothing -> () -> m ()
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
Just ScenarioInfo
si -> do
let segments :: [FilePath]
segments = FilePath -> [FilePath]
splitDirectories FilePath
p
case [FilePath]
segments of
FilePath
firstDir : [FilePath]
_ -> do
Bool -> m () -> m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Bool
won Bool -> Bool -> Bool
&& FilePath
firstDir FilePath -> FilePath -> Bool
forall a. Eq a => a -> a -> Bool
== FilePath
tutorialsDirname) (m () -> m ()) -> m () -> m ()
forall a b. (a -> b) -> a -> b
$
ZonedTime -> Maybe FilePath -> CategorizedAchievement -> m ()
forall (m :: * -> *).
(MonadIO m, MonadState AppState m) =>
ZonedTime -> Maybe FilePath -> CategorizedAchievement -> m ()
attainAchievement' ZonedTime
t (FilePath -> Maybe FilePath
forall a. a -> Maybe a
Just FilePath
p) (GlobalAchievement -> CategorizedAchievement
GlobalAchievement GlobalAchievement
CompletedSingleTutorial)
[FilePath]
_ -> () -> m ()
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ FilePath -> ScenarioInfo -> IO ()
saveScenarioInfo FilePath
p ScenarioInfo
si
Maybe ScenarioInfo -> m (Maybe ScenarioInfo)
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ScenarioInfo
status
saveScenarioInfoOnFinishNocheat :: (MonadIO m, MonadState AppState m) => m ()
saveScenarioInfoOnFinishNocheat :: forall (m :: * -> *). (MonadIO m, MonadState AppState m) => m ()
saveScenarioInfoOnFinishNocheat = do
Bool
cheat <- Getting Bool AppState Bool -> m Bool
forall s (m :: * -> *) a. MonadState s m => Getting a s a -> m a
use (Getting Bool AppState Bool -> m Bool)
-> Getting Bool AppState Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ (UIState -> Const Bool UIState) -> AppState -> Const Bool AppState
Lens' AppState UIState
uiState ((UIState -> Const Bool UIState)
-> AppState -> Const Bool AppState)
-> ((Bool -> Const Bool Bool) -> UIState -> Const Bool UIState)
-> Getting Bool AppState Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Bool -> Const Bool Bool) -> UIState -> Const Bool UIState
Lens' UIState Bool
uiCheatMode
Bool -> m () -> m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless Bool
cheat (m () -> m ()) -> m () -> m ()
forall a b. (a -> b) -> a -> b
$ do
m (Maybe FilePath)
forall (m :: * -> *).
(MonadIO m, MonadState AppState m) =>
m (Maybe FilePath)
getNormalizedCurrentScenarioPath m (Maybe FilePath) -> (Maybe FilePath -> m ()) -> m ()
forall a b. m a -> (a -> m b) -> m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Maybe FilePath
Nothing -> () -> m ()
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
Just FilePath
p -> m (Maybe ScenarioInfo) -> m ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (m (Maybe ScenarioInfo) -> m ()) -> m (Maybe ScenarioInfo) -> m ()
forall a b. (a -> b) -> a -> b
$ FilePath -> m (Maybe ScenarioInfo)
forall (m :: * -> *).
(MonadIO m, MonadState AppState m) =>
FilePath -> m (Maybe ScenarioInfo)
saveScenarioInfoOnFinish FilePath
p
saveScenarioInfoOnQuit :: (MonadIO m, MonadState AppState m) => m ()
saveScenarioInfoOnQuit :: forall (m :: * -> *). (MonadIO m, MonadState AppState m) => m ()
saveScenarioInfoOnQuit = do
Bool
cheat <- Getting Bool AppState Bool -> m Bool
forall s (m :: * -> *) a. MonadState s m => Getting a s a -> m a
use (Getting Bool AppState Bool -> m Bool)
-> Getting Bool AppState Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ (UIState -> Const Bool UIState) -> AppState -> Const Bool AppState
Lens' AppState UIState
uiState ((UIState -> Const Bool UIState)
-> AppState -> Const Bool AppState)
-> ((Bool -> Const Bool Bool) -> UIState -> Const Bool UIState)
-> Getting Bool AppState Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Bool -> Const Bool Bool) -> UIState -> Const Bool UIState
Lens' UIState Bool
uiCheatMode
Bool -> m () -> m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless Bool
cheat (m () -> m ()) -> m () -> m ()
forall a b. (a -> b) -> a -> b
$ do
m (Maybe FilePath)
forall (m :: * -> *).
(MonadIO m, MonadState AppState m) =>
m (Maybe FilePath)
getNormalizedCurrentScenarioPath m (Maybe FilePath) -> (Maybe FilePath -> m ()) -> m ()
forall a b. m a -> (a -> m b) -> m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Maybe FilePath
Nothing -> () -> m ()
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
Just FilePath
p -> do
Maybe ScenarioInfo
maybeSi <- FilePath -> m (Maybe ScenarioInfo)
forall (m :: * -> *).
(MonadIO m, MonadState AppState m) =>
FilePath -> m (Maybe ScenarioInfo)
saveScenarioInfoOnFinish FilePath
p
Maybe ScenarioInfo -> (ScenarioInfo -> m ()) -> m ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_
Maybe ScenarioInfo
maybeSi
( (UIState -> Identity UIState) -> AppState -> Identity AppState
Lens' AppState UIState
uiState
((UIState -> Identity UIState) -> AppState -> Identity AppState)
-> ((ScenarioInfo -> Identity ScenarioInfo)
-> UIState -> Identity UIState)
-> (ScenarioInfo -> Identity ScenarioInfo)
-> AppState
-> Identity AppState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Menu -> Identity Menu) -> UIState -> Identity UIState
Lens' UIState Menu
uiMenu
((Menu -> Identity Menu) -> UIState -> Identity UIState)
-> ((ScenarioInfo -> Identity ScenarioInfo)
-> Menu -> Identity Menu)
-> (ScenarioInfo -> Identity ScenarioInfo)
-> UIState
-> Identity UIState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (NonEmpty (List Name ScenarioItem)
-> Identity (NonEmpty (List Name ScenarioItem)))
-> Menu -> Identity Menu
Prism' Menu (NonEmpty (List Name ScenarioItem))
_NewGameMenu
((NonEmpty (List Name ScenarioItem)
-> Identity (NonEmpty (List Name ScenarioItem)))
-> Menu -> Identity Menu)
-> ((ScenarioInfo -> Identity ScenarioInfo)
-> NonEmpty (List Name ScenarioItem)
-> Identity (NonEmpty (List Name ScenarioItem)))
-> (ScenarioInfo -> Identity ScenarioInfo)
-> Menu
-> Identity Menu
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Index (NonEmpty (List Name ScenarioItem))
-> Traversal'
(NonEmpty (List Name ScenarioItem))
(IxValue (NonEmpty (List Name ScenarioItem)))
forall m. Ixed m => Index m -> Traversal' m (IxValue m)
ix Int
Index (NonEmpty (List Name ScenarioItem))
0
((List Name ScenarioItem -> Identity (List Name ScenarioItem))
-> NonEmpty (List Name ScenarioItem)
-> Identity (NonEmpty (List Name ScenarioItem)))
-> ((ScenarioInfo -> Identity ScenarioInfo)
-> List Name ScenarioItem -> Identity (List Name ScenarioItem))
-> (ScenarioInfo -> Identity ScenarioInfo)
-> NonEmpty (List Name ScenarioItem)
-> Identity (NonEmpty (List Name ScenarioItem))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ScenarioItem -> Identity ScenarioItem)
-> List Name ScenarioItem -> Identity (List Name ScenarioItem)
Traversal' (List Name ScenarioItem) ScenarioItem
forall (t :: * -> *) e n.
(Splittable t, Traversable t, Semigroup (t e)) =>
Traversal' (GenericList n t e) e
BL.listSelectedElementL
((ScenarioItem -> Identity ScenarioItem)
-> List Name ScenarioItem -> Identity (List Name ScenarioItem))
-> ((ScenarioInfo -> Identity ScenarioInfo)
-> ScenarioItem -> Identity ScenarioItem)
-> (ScenarioInfo -> Identity ScenarioInfo)
-> List Name ScenarioItem
-> Identity (List Name ScenarioItem)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ScenarioInfoPair -> Identity ScenarioInfoPair)
-> ScenarioItem -> Identity ScenarioItem
Prism' ScenarioItem ScenarioInfoPair
_SISingle
((ScenarioInfoPair -> Identity ScenarioInfoPair)
-> ScenarioItem -> Identity ScenarioItem)
-> ((ScenarioInfo -> Identity ScenarioInfo)
-> ScenarioInfoPair -> Identity ScenarioInfoPair)
-> (ScenarioInfo -> Identity ScenarioInfo)
-> ScenarioItem
-> Identity ScenarioItem
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ScenarioInfo -> Identity ScenarioInfo)
-> ScenarioInfoPair -> Identity ScenarioInfoPair
forall s t a b. Field2 s t a b => Lens s t a b
Lens ScenarioInfoPair ScenarioInfoPair ScenarioInfo ScenarioInfo
_2
((ScenarioInfo -> Identity ScenarioInfo)
-> AppState -> Identity AppState)
-> ScenarioInfo -> m ()
forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.=
)
Maybe FilePath
curPath <- Getting (First FilePath) AppState FilePath -> m (Maybe FilePath)
forall s (m :: * -> *) a.
MonadState s m =>
Getting (First a) s a -> m (Maybe a)
preuse (Getting (First FilePath) AppState FilePath -> m (Maybe FilePath))
-> Getting (First FilePath) AppState FilePath -> m (Maybe FilePath)
forall a b. (a -> b) -> a -> b
$ (UIState -> Const (First FilePath) UIState)
-> AppState -> Const (First FilePath) AppState
Lens' AppState UIState
uiState ((UIState -> Const (First FilePath) UIState)
-> AppState -> Const (First FilePath) AppState)
-> ((FilePath -> Const (First FilePath) FilePath)
-> UIState -> Const (First FilePath) UIState)
-> Getting (First FilePath) AppState FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Menu -> Const (First FilePath) Menu)
-> UIState -> Const (First FilePath) UIState
Lens' UIState Menu
uiMenu ((Menu -> Const (First FilePath) Menu)
-> UIState -> Const (First FilePath) UIState)
-> ((FilePath -> Const (First FilePath) FilePath)
-> Menu -> Const (First FilePath) Menu)
-> (FilePath -> Const (First FilePath) FilePath)
-> UIState
-> Const (First FilePath) UIState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (NonEmpty (List Name ScenarioItem)
-> Const (First FilePath) (NonEmpty (List Name ScenarioItem)))
-> Menu -> Const (First FilePath) Menu
Prism' Menu (NonEmpty (List Name ScenarioItem))
_NewGameMenu ((NonEmpty (List Name ScenarioItem)
-> Const (First FilePath) (NonEmpty (List Name ScenarioItem)))
-> Menu -> Const (First FilePath) Menu)
-> ((FilePath -> Const (First FilePath) FilePath)
-> NonEmpty (List Name ScenarioItem)
-> Const (First FilePath) (NonEmpty (List Name ScenarioItem)))
-> (FilePath -> Const (First FilePath) FilePath)
-> Menu
-> Const (First FilePath) Menu
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Index (NonEmpty (List Name ScenarioItem))
-> Traversal'
(NonEmpty (List Name ScenarioItem))
(IxValue (NonEmpty (List Name ScenarioItem)))
forall m. Ixed m => Index m -> Traversal' m (IxValue m)
ix Int
Index (NonEmpty (List Name ScenarioItem))
0 ((List Name ScenarioItem
-> Const (First FilePath) (List Name ScenarioItem))
-> NonEmpty (List Name ScenarioItem)
-> Const (First FilePath) (NonEmpty (List Name ScenarioItem)))
-> ((FilePath -> Const (First FilePath) FilePath)
-> List Name ScenarioItem
-> Const (First FilePath) (List Name ScenarioItem))
-> (FilePath -> Const (First FilePath) FilePath)
-> NonEmpty (List Name ScenarioItem)
-> Const (First FilePath) (NonEmpty (List Name ScenarioItem))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ScenarioItem -> Const (First FilePath) ScenarioItem)
-> List Name ScenarioItem
-> Const (First FilePath) (List Name ScenarioItem)
Traversal' (List Name ScenarioItem) ScenarioItem
forall (t :: * -> *) e n.
(Splittable t, Traversable t, Semigroup (t e)) =>
Traversal' (GenericList n t e) e
BL.listSelectedElementL ((ScenarioItem -> Const (First FilePath) ScenarioItem)
-> List Name ScenarioItem
-> Const (First FilePath) (List Name ScenarioItem))
-> ((FilePath -> Const (First FilePath) FilePath)
-> ScenarioItem -> Const (First FilePath) ScenarioItem)
-> (FilePath -> Const (First FilePath) FilePath)
-> List Name ScenarioItem
-> Const (First FilePath) (List Name ScenarioItem)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ScenarioInfoPair -> Const (First FilePath) ScenarioInfoPair)
-> ScenarioItem -> Const (First FilePath) ScenarioItem
Prism' ScenarioItem ScenarioInfoPair
_SISingle ((ScenarioInfoPair -> Const (First FilePath) ScenarioInfoPair)
-> ScenarioItem -> Const (First FilePath) ScenarioItem)
-> ((FilePath -> Const (First FilePath) FilePath)
-> ScenarioInfoPair -> Const (First FilePath) ScenarioInfoPair)
-> (FilePath -> Const (First FilePath) FilePath)
-> ScenarioItem
-> Const (First FilePath) ScenarioItem
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ScenarioInfo -> Const (First FilePath) ScenarioInfo)
-> ScenarioInfoPair -> Const (First FilePath) ScenarioInfoPair
forall s t a b. Field2 s t a b => Lens s t a b
Lens ScenarioInfoPair ScenarioInfoPair ScenarioInfo ScenarioInfo
_2 ((ScenarioInfo -> Const (First FilePath) ScenarioInfo)
-> ScenarioInfoPair -> Const (First FilePath) ScenarioInfoPair)
-> ((FilePath -> Const (First FilePath) FilePath)
-> ScenarioInfo -> Const (First FilePath) ScenarioInfo)
-> (FilePath -> Const (First FilePath) FilePath)
-> ScenarioInfoPair
-> Const (First FilePath) ScenarioInfoPair
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (FilePath -> Const (First FilePath) FilePath)
-> ScenarioInfo -> Const (First FilePath) ScenarioInfo
Lens' ScenarioInfo FilePath
scenarioPath
ScenarioCollection
sc <- Getting ScenarioCollection AppState ScenarioCollection
-> m ScenarioCollection
forall s (m :: * -> *) a. MonadState s m => Getting a s a -> m a
use (Getting ScenarioCollection AppState ScenarioCollection
-> m ScenarioCollection)
-> Getting ScenarioCollection AppState ScenarioCollection
-> m ScenarioCollection
forall a b. (a -> b) -> a -> b
$ (RuntimeState -> Const ScenarioCollection RuntimeState)
-> AppState -> Const ScenarioCollection AppState
Lens' AppState RuntimeState
runtimeState ((RuntimeState -> Const ScenarioCollection RuntimeState)
-> AppState -> Const ScenarioCollection AppState)
-> ((ScenarioCollection
-> Const ScenarioCollection ScenarioCollection)
-> RuntimeState -> Const ScenarioCollection RuntimeState)
-> Getting ScenarioCollection AppState ScenarioCollection
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ScenarioCollection -> Const ScenarioCollection ScenarioCollection)
-> RuntimeState -> Const ScenarioCollection RuntimeState
Lens' RuntimeState ScenarioCollection
scenarios
Maybe Menu -> (Menu -> m ()) -> m ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ (Bool -> ScenarioCollection -> FilePath -> Maybe Menu
mkNewGameMenu Bool
cheat ScenarioCollection
sc (FilePath -> Maybe FilePath -> FilePath
forall a. a -> Maybe a -> a
fromMaybe FilePath
p Maybe FilePath
curPath)) ((UIState -> Identity UIState) -> AppState -> Identity AppState
Lens' AppState UIState
uiState ((UIState -> Identity UIState) -> AppState -> Identity AppState)
-> ((Menu -> Identity Menu) -> UIState -> Identity UIState)
-> (Menu -> Identity Menu)
-> AppState
-> Identity AppState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Menu -> Identity Menu) -> UIState -> Identity UIState
Lens' UIState Menu
uiMenu ((Menu -> Identity Menu) -> AppState -> Identity AppState)
-> Menu -> m ()
forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.=)