module Swarm.TUI.Launch.Controller where
import Brick hiding (Direction, Location)
import Brick.Focus
import Brick.Widgets.Edit (handleEditorEvent)
import Brick.Widgets.FileBrowser
import Brick.Widgets.FileBrowser qualified as FB
import Control.Lens
import Control.Monad (forM_, when)
import Control.Monad.IO.Class (liftIO)
import Data.List.Extra (enumerate)
import Data.Maybe (listToMaybe)
import Graphics.Vty qualified as V
import Swarm.Game.Scenario.Status (ParameterizableLaunchParams (LaunchParams))
import Swarm.Game.ScenarioInfo
import Swarm.TUI.Controller.Util
import Swarm.TUI.Launch.Model
import Swarm.TUI.Launch.Prep (initFileBrowserWidget, makeFocusRingWith, parseSeedInput, parseWidgetParams, toValidatedParams)
import Swarm.TUI.Model
import Swarm.TUI.Model.Name
import Swarm.TUI.Model.StateUpdate
import Swarm.TUI.Model.UI
updateFocusRing :: EditingLaunchParams -> EventM Name LaunchOptions ()
updateFocusRing :: EditingLaunchParams -> EventM Name LaunchOptions ()
updateFocusRing EditingLaunchParams
parsedParams = do
FocusRing Name
currentRing <- Getting (FocusRing Name) LaunchOptions (FocusRing Name)
-> EventM Name LaunchOptions (FocusRing Name)
forall s (m :: * -> *) a. MonadState s m => Getting a s a -> m a
use (Getting (FocusRing Name) LaunchOptions (FocusRing Name)
-> EventM Name LaunchOptions (FocusRing Name))
-> Getting (FocusRing Name) LaunchOptions (FocusRing Name)
-> EventM Name LaunchOptions (FocusRing Name)
forall a b. (a -> b) -> a -> b
$ (LaunchControls -> Const (FocusRing Name) LaunchControls)
-> LaunchOptions -> Const (FocusRing Name) LaunchOptions
Lens' LaunchOptions LaunchControls
controls ((LaunchControls -> Const (FocusRing Name) LaunchControls)
-> LaunchOptions -> Const (FocusRing Name) LaunchOptions)
-> ((FocusRing Name -> Const (FocusRing Name) (FocusRing Name))
-> LaunchControls -> Const (FocusRing Name) LaunchControls)
-> Getting (FocusRing Name) LaunchOptions (FocusRing Name)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (FocusRing Name -> Const (FocusRing Name) (FocusRing Name))
-> LaunchControls -> Const (FocusRing Name) LaunchControls
Lens' LaunchControls (FocusRing Name)
scenarioConfigFocusRing
let eitherLaunchParams :: Either Text ValidatedLaunchParams
eitherLaunchParams = EditingLaunchParams -> Either Text ValidatedLaunchParams
toValidatedParams EditingLaunchParams
parsedParams
modifyRingMembers :: [ScenarioConfigPanelFocusable] -> [ScenarioConfigPanelFocusable]
modifyRingMembers = case Either Text ValidatedLaunchParams
eitherLaunchParams of
Left Text
_ -> (ScenarioConfigPanelFocusable -> Bool)
-> [ScenarioConfigPanelFocusable] -> [ScenarioConfigPanelFocusable]
forall a. (a -> Bool) -> [a] -> [a]
filter (ScenarioConfigPanelFocusable
-> ScenarioConfigPanelFocusable -> Bool
forall a. Eq a => a -> a -> Bool
/= ScenarioConfigPanelFocusable
StartGameButton)
Right ValidatedLaunchParams
_ -> [ScenarioConfigPanelFocusable] -> [ScenarioConfigPanelFocusable]
forall a. a -> a
id
maybeCurrentFocus :: Maybe Name
maybeCurrentFocus = FocusRing Name -> Maybe Name
forall n. FocusRing n -> Maybe n
focusGetCurrent FocusRing Name
currentRing
refocusRing :: FocusRing Name -> FocusRing Name
refocusRing = (FocusRing Name -> FocusRing Name)
-> (Name -> FocusRing Name -> FocusRing Name)
-> Maybe Name
-> FocusRing Name
-> FocusRing Name
forall b a. b -> (a -> b) -> Maybe a -> b
maybe FocusRing Name -> FocusRing Name
forall a. a -> a
id Name -> FocusRing Name -> FocusRing Name
forall n. Eq n => n -> FocusRing n -> FocusRing n
focusSetCurrent Maybe Name
maybeCurrentFocus
(LaunchControls -> Identity LaunchControls)
-> LaunchOptions -> Identity LaunchOptions
Lens' LaunchOptions LaunchControls
controls ((LaunchControls -> Identity LaunchControls)
-> LaunchOptions -> Identity LaunchOptions)
-> ((FocusRing Name -> Identity (FocusRing Name))
-> LaunchControls -> Identity LaunchControls)
-> (FocusRing Name -> Identity (FocusRing Name))
-> LaunchOptions
-> Identity LaunchOptions
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (FocusRing Name -> Identity (FocusRing Name))
-> LaunchControls -> Identity LaunchControls
Lens' LaunchControls (FocusRing Name)
scenarioConfigFocusRing ((FocusRing Name -> Identity (FocusRing Name))
-> LaunchOptions -> Identity LaunchOptions)
-> FocusRing Name -> EventM Name LaunchOptions ()
forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= FocusRing Name -> FocusRing Name
refocusRing ([ScenarioConfigPanelFocusable] -> FocusRing Name
makeFocusRingWith ([ScenarioConfigPanelFocusable] -> FocusRing Name)
-> [ScenarioConfigPanelFocusable] -> FocusRing Name
forall a b. (a -> b) -> a -> b
$ [ScenarioConfigPanelFocusable] -> [ScenarioConfigPanelFocusable]
modifyRingMembers [ScenarioConfigPanelFocusable]
forall a. (Enum a, Bounded a) => [a]
enumerate)
cacheValidatedInputs :: EventM Name LaunchOptions ()
cacheValidatedInputs :: EventM Name LaunchOptions ()
cacheValidatedInputs = do
LaunchControls
launchControls <- Getting LaunchControls LaunchOptions LaunchControls
-> EventM Name LaunchOptions LaunchControls
forall s (m :: * -> *) a. MonadState s m => Getting a s a -> m a
use Getting LaunchControls LaunchOptions LaunchControls
Lens' LaunchOptions LaunchControls
controls
EditingLaunchParams
parsedParams <- IO EditingLaunchParams
-> EventM Name LaunchOptions EditingLaunchParams
forall a. IO a -> EventM Name LaunchOptions a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO EditingLaunchParams
-> EventM Name LaunchOptions EditingLaunchParams)
-> IO EditingLaunchParams
-> EventM Name LaunchOptions EditingLaunchParams
forall a b. (a -> b) -> a -> b
$ LaunchControls -> IO EditingLaunchParams
parseWidgetParams LaunchControls
launchControls
(EditingLaunchParams -> Identity EditingLaunchParams)
-> LaunchOptions -> Identity LaunchOptions
Lens' LaunchOptions EditingLaunchParams
editingParams ((EditingLaunchParams -> Identity EditingLaunchParams)
-> LaunchOptions -> Identity LaunchOptions)
-> EditingLaunchParams -> EventM Name LaunchOptions ()
forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= EditingLaunchParams
parsedParams
EditingLaunchParams -> EventM Name LaunchOptions ()
updateFocusRing EditingLaunchParams
parsedParams
cacheValidatedSeedInput :: EventM Name LaunchOptions ()
cacheValidatedSeedInput :: EventM Name LaunchOptions ()
cacheValidatedSeedInput = do
Editor Text Name
seedEditor <- Getting (Editor Text Name) LaunchOptions (Editor Text Name)
-> EventM Name LaunchOptions (Editor Text Name)
forall s (m :: * -> *) a. MonadState s m => Getting a s a -> m a
use (Getting (Editor Text Name) LaunchOptions (Editor Text Name)
-> EventM Name LaunchOptions (Editor Text Name))
-> Getting (Editor Text Name) LaunchOptions (Editor Text Name)
-> EventM Name LaunchOptions (Editor Text Name)
forall a b. (a -> b) -> a -> b
$ (LaunchControls -> Const (Editor Text Name) LaunchControls)
-> LaunchOptions -> Const (Editor Text Name) LaunchOptions
Lens' LaunchOptions LaunchControls
controls ((LaunchControls -> Const (Editor Text Name) LaunchControls)
-> LaunchOptions -> Const (Editor Text Name) LaunchOptions)
-> ((Editor Text Name
-> Const (Editor Text Name) (Editor Text Name))
-> LaunchControls -> Const (Editor Text Name) LaunchControls)
-> Getting (Editor Text Name) LaunchOptions (Editor Text Name)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Editor Text Name -> Const (Editor Text Name) (Editor Text Name))
-> LaunchControls -> Const (Editor Text Name) LaunchControls
Lens' LaunchControls (Editor Text Name)
seedValueEditor
let eitherMaybeSeed :: Either Text (Maybe Seed)
eitherMaybeSeed = Editor Text Name -> Either Text (Maybe Seed)
parseSeedInput Editor Text Name
seedEditor
LaunchParams Either Text (Maybe Seed)
_ Either Text (Maybe CodeToRun)
eitherParsedCode <- Getting EditingLaunchParams LaunchOptions EditingLaunchParams
-> EventM Name LaunchOptions EditingLaunchParams
forall s (m :: * -> *) a. MonadState s m => Getting a s a -> m a
use Getting EditingLaunchParams LaunchOptions EditingLaunchParams
Lens' LaunchOptions EditingLaunchParams
editingParams
let newParams :: EditingLaunchParams
newParams = Either Text (Maybe Seed)
-> Either Text (Maybe CodeToRun) -> EditingLaunchParams
forall code (f :: * -> *).
f (Maybe Seed)
-> f (Maybe code) -> ParameterizableLaunchParams code f
LaunchParams Either Text (Maybe Seed)
eitherMaybeSeed Either Text (Maybe CodeToRun)
eitherParsedCode
(EditingLaunchParams -> Identity EditingLaunchParams)
-> LaunchOptions -> Identity LaunchOptions
Lens' LaunchOptions EditingLaunchParams
editingParams ((EditingLaunchParams -> Identity EditingLaunchParams)
-> LaunchOptions -> Identity LaunchOptions)
-> EditingLaunchParams -> EventM Name LaunchOptions ()
forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= EditingLaunchParams
newParams
EditingLaunchParams -> EventM Name LaunchOptions ()
updateFocusRing EditingLaunchParams
newParams
handleFBEvent ::
BrickEvent Name AppEvent ->
EventM Name AppState ()
handleFBEvent :: BrickEvent Name AppEvent -> EventM Name AppState ()
handleFBEvent BrickEvent Name AppEvent
ev = do
FileBrowser Name
fb <- Getting (FileBrowser Name) AppState (FileBrowser Name)
-> EventM Name AppState (FileBrowser Name)
forall s (m :: * -> *) a. MonadState s m => Getting a s a -> m a
use (Getting (FileBrowser Name) AppState (FileBrowser Name)
-> EventM Name AppState (FileBrowser Name))
-> Getting (FileBrowser Name) AppState (FileBrowser Name)
-> EventM Name AppState (FileBrowser Name)
forall a b. (a -> b) -> a -> b
$ (UIState -> Const (FileBrowser Name) UIState)
-> AppState -> Const (FileBrowser Name) AppState
Lens' AppState UIState
uiState ((UIState -> Const (FileBrowser Name) UIState)
-> AppState -> Const (FileBrowser Name) AppState)
-> ((FileBrowser Name
-> Const (FileBrowser Name) (FileBrowser Name))
-> UIState -> Const (FileBrowser Name) UIState)
-> Getting (FileBrowser Name) AppState (FileBrowser Name)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (LaunchOptions -> Const (FileBrowser Name) LaunchOptions)
-> UIState -> Const (FileBrowser Name) UIState
Lens' UIState LaunchOptions
uiLaunchConfig ((LaunchOptions -> Const (FileBrowser Name) LaunchOptions)
-> UIState -> Const (FileBrowser Name) UIState)
-> ((FileBrowser Name
-> Const (FileBrowser Name) (FileBrowser Name))
-> LaunchOptions -> Const (FileBrowser Name) LaunchOptions)
-> (FileBrowser Name
-> Const (FileBrowser Name) (FileBrowser Name))
-> UIState
-> Const (FileBrowser Name) UIState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (LaunchControls -> Const (FileBrowser Name) LaunchControls)
-> LaunchOptions -> Const (FileBrowser Name) LaunchOptions
Lens' LaunchOptions LaunchControls
controls ((LaunchControls -> Const (FileBrowser Name) LaunchControls)
-> LaunchOptions -> Const (FileBrowser Name) LaunchOptions)
-> ((FileBrowser Name
-> Const (FileBrowser Name) (FileBrowser Name))
-> LaunchControls -> Const (FileBrowser Name) LaunchControls)
-> (FileBrowser Name
-> Const (FileBrowser Name) (FileBrowser Name))
-> LaunchOptions
-> Const (FileBrowser Name) LaunchOptions
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (FileBrowserControl -> Const (FileBrowser Name) FileBrowserControl)
-> LaunchControls -> Const (FileBrowser Name) LaunchControls
Lens' LaunchControls FileBrowserControl
fileBrowser ((FileBrowserControl
-> Const (FileBrowser Name) FileBrowserControl)
-> LaunchControls -> Const (FileBrowser Name) LaunchControls)
-> ((FileBrowser Name
-> Const (FileBrowser Name) (FileBrowser Name))
-> FileBrowserControl
-> Const (FileBrowser Name) FileBrowserControl)
-> (FileBrowser Name
-> Const (FileBrowser Name) (FileBrowser Name))
-> LaunchControls
-> Const (FileBrowser Name) LaunchControls
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (FileBrowser Name -> Const (FileBrowser Name) (FileBrowser Name))
-> FileBrowserControl
-> Const (FileBrowser Name) FileBrowserControl
Lens' FileBrowserControl (FileBrowser Name)
fbWidget
let isSearching :: Bool
isSearching = FileBrowser Name -> Bool
forall n. FileBrowser n -> Bool
fileBrowserIsSearching FileBrowser Name
fb
case (Bool
isSearching, BrickEvent Name AppEvent
ev) of
(Bool
False, Key Key
V.KEsc) -> EventM Name AppState ()
closeModal
(Bool
False, CharKey Char
'q') -> EventM Name AppState ()
closeModal
(Bool
False, ControlChar Char
'q') -> EventM Name AppState ()
closeModal
(Bool
False, CharKey Char
' ') -> () -> EventM Name AppState ()
forall a. a -> EventM Name AppState a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
(Bool
_, VtyEvent Event
e) -> do
(Bool
shouldClose, Maybe FilePath
maybeSingleFile) <- LensLike'
(Zoomed (EventM Name (FileBrowser Name)) (Bool, Maybe FilePath))
AppState
(FileBrowser Name)
-> EventM Name (FileBrowser Name) (Bool, Maybe FilePath)
-> EventM Name AppState (Bool, Maybe FilePath)
forall c.
LensLike'
(Zoomed (EventM Name (FileBrowser Name)) c)
AppState
(FileBrowser Name)
-> EventM Name (FileBrowser Name) c -> EventM Name AppState c
forall (m :: * -> *) (n :: * -> *) s t c.
Zoom m n s t =>
LensLike' (Zoomed m c) t s -> m c -> n c
Brick.zoom ((UIState
-> Focusing
(StateT (EventState Name) IO) (Bool, Maybe FilePath) UIState)
-> AppState
-> Focusing
(StateT (EventState Name) IO) (Bool, Maybe FilePath) AppState
Lens' AppState UIState
uiState ((UIState
-> Focusing
(StateT (EventState Name) IO) (Bool, Maybe FilePath) UIState)
-> AppState
-> Focusing
(StateT (EventState Name) IO) (Bool, Maybe FilePath) AppState)
-> ((FileBrowser Name
-> Focusing
(StateT (EventState Name) IO)
(Bool, Maybe FilePath)
(FileBrowser Name))
-> UIState
-> Focusing
(StateT (EventState Name) IO) (Bool, Maybe FilePath) UIState)
-> (FileBrowser Name
-> Focusing
(StateT (EventState Name) IO)
(Bool, Maybe FilePath)
(FileBrowser Name))
-> AppState
-> Focusing
(StateT (EventState Name) IO) (Bool, Maybe FilePath) AppState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (LaunchOptions
-> Focusing
(StateT (EventState Name) IO) (Bool, Maybe FilePath) LaunchOptions)
-> UIState
-> Focusing
(StateT (EventState Name) IO) (Bool, Maybe FilePath) UIState
Lens' UIState LaunchOptions
uiLaunchConfig ((LaunchOptions
-> Focusing
(StateT (EventState Name) IO) (Bool, Maybe FilePath) LaunchOptions)
-> UIState
-> Focusing
(StateT (EventState Name) IO) (Bool, Maybe FilePath) UIState)
-> ((FileBrowser Name
-> Focusing
(StateT (EventState Name) IO)
(Bool, Maybe FilePath)
(FileBrowser Name))
-> LaunchOptions
-> Focusing
(StateT (EventState Name) IO) (Bool, Maybe FilePath) LaunchOptions)
-> (FileBrowser Name
-> Focusing
(StateT (EventState Name) IO)
(Bool, Maybe FilePath)
(FileBrowser Name))
-> UIState
-> Focusing
(StateT (EventState Name) IO) (Bool, Maybe FilePath) UIState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (LaunchControls
-> Focusing
(StateT (EventState Name) IO)
(Bool, Maybe FilePath)
LaunchControls)
-> LaunchOptions
-> Focusing
(StateT (EventState Name) IO) (Bool, Maybe FilePath) LaunchOptions
Lens' LaunchOptions LaunchControls
controls ((LaunchControls
-> Focusing
(StateT (EventState Name) IO)
(Bool, Maybe FilePath)
LaunchControls)
-> LaunchOptions
-> Focusing
(StateT (EventState Name) IO) (Bool, Maybe FilePath) LaunchOptions)
-> ((FileBrowser Name
-> Focusing
(StateT (EventState Name) IO)
(Bool, Maybe FilePath)
(FileBrowser Name))
-> LaunchControls
-> Focusing
(StateT (EventState Name) IO)
(Bool, Maybe FilePath)
LaunchControls)
-> (FileBrowser Name
-> Focusing
(StateT (EventState Name) IO)
(Bool, Maybe FilePath)
(FileBrowser Name))
-> LaunchOptions
-> Focusing
(StateT (EventState Name) IO) (Bool, Maybe FilePath) LaunchOptions
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (FileBrowserControl
-> Focusing
(StateT (EventState Name) IO)
(Bool, Maybe FilePath)
FileBrowserControl)
-> LaunchControls
-> Focusing
(StateT (EventState Name) IO) (Bool, Maybe FilePath) LaunchControls
Lens' LaunchControls FileBrowserControl
fileBrowser ((FileBrowserControl
-> Focusing
(StateT (EventState Name) IO)
(Bool, Maybe FilePath)
FileBrowserControl)
-> LaunchControls
-> Focusing
(StateT (EventState Name) IO)
(Bool, Maybe FilePath)
LaunchControls)
-> ((FileBrowser Name
-> Focusing
(StateT (EventState Name) IO)
(Bool, Maybe FilePath)
(FileBrowser Name))
-> FileBrowserControl
-> Focusing
(StateT (EventState Name) IO)
(Bool, Maybe FilePath)
FileBrowserControl)
-> (FileBrowser Name
-> Focusing
(StateT (EventState Name) IO)
(Bool, Maybe FilePath)
(FileBrowser Name))
-> LaunchControls
-> Focusing
(StateT (EventState Name) IO) (Bool, Maybe FilePath) LaunchControls
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (FileBrowser Name
-> Focusing
(StateT (EventState Name) IO)
(Bool, Maybe FilePath)
(FileBrowser Name))
-> FileBrowserControl
-> Focusing
(StateT (EventState Name) IO)
(Bool, Maybe FilePath)
FileBrowserControl
Lens' FileBrowserControl (FileBrowser Name)
fbWidget) (EventM Name (FileBrowser Name) (Bool, Maybe FilePath)
-> EventM Name AppState (Bool, Maybe FilePath))
-> EventM Name (FileBrowser Name) (Bool, Maybe FilePath)
-> EventM Name AppState (Bool, Maybe FilePath)
forall a b. (a -> b) -> a -> b
$ do
Event -> EventM Name (FileBrowser Name) ()
forall n. Ord n => Event -> EventM n (FileBrowser n) ()
handleFileBrowserEvent Event
e
case Event
e of
V.EvKey Key
V.KEnter [] -> do
FileBrowser Name
b' <- EventM Name (FileBrowser Name) (FileBrowser Name)
forall s (m :: * -> *). MonadState s m => m s
get
case FileBrowser Name -> [FileInfo]
forall n. FileBrowser n -> [FileInfo]
FB.fileBrowserSelection FileBrowser Name
b' of
[] -> (Bool, Maybe FilePath)
-> EventM Name (FileBrowser Name) (Bool, Maybe FilePath)
forall a. a -> EventM Name (FileBrowser Name) a
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
False, Maybe FilePath
forall a. Maybe a
Nothing)
[FileInfo]
xs -> (Bool, Maybe FilePath)
-> EventM Name (FileBrowser Name) (Bool, Maybe FilePath)
forall a. a -> EventM Name (FileBrowser Name) a
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
True, FileInfo -> FilePath
FB.fileInfoFilePath (FileInfo -> FilePath) -> Maybe FileInfo -> Maybe FilePath
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [FileInfo] -> Maybe FileInfo
forall a. [a] -> Maybe a
listToMaybe [FileInfo]
xs)
Event
_ -> (Bool, Maybe FilePath)
-> EventM Name (FileBrowser Name) (Bool, Maybe FilePath)
forall a. a -> EventM Name (FileBrowser Name) a
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
False, Maybe FilePath
forall a. Maybe a
Nothing)
Bool -> EventM Name AppState () -> EventM Name AppState ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
shouldClose (EventM Name AppState () -> EventM Name AppState ())
-> EventM Name AppState () -> EventM Name AppState ()
forall a b. (a -> b) -> a -> b
$ do
(UIState -> Identity UIState) -> AppState -> Identity AppState
Lens' AppState UIState
uiState ((UIState -> Identity UIState) -> AppState -> Identity AppState)
-> ((Maybe FilePath -> Identity (Maybe FilePath))
-> UIState -> Identity UIState)
-> (Maybe FilePath -> Identity (Maybe FilePath))
-> AppState
-> Identity AppState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (LaunchOptions -> Identity LaunchOptions)
-> UIState -> Identity UIState
Lens' UIState LaunchOptions
uiLaunchConfig ((LaunchOptions -> Identity LaunchOptions)
-> UIState -> Identity UIState)
-> ((Maybe FilePath -> Identity (Maybe FilePath))
-> LaunchOptions -> Identity LaunchOptions)
-> (Maybe FilePath -> Identity (Maybe FilePath))
-> UIState
-> Identity UIState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (LaunchControls -> Identity LaunchControls)
-> LaunchOptions -> Identity LaunchOptions
Lens' LaunchOptions LaunchControls
controls ((LaunchControls -> Identity LaunchControls)
-> LaunchOptions -> Identity LaunchOptions)
-> ((Maybe FilePath -> Identity (Maybe FilePath))
-> LaunchControls -> Identity LaunchControls)
-> (Maybe FilePath -> Identity (Maybe FilePath))
-> LaunchOptions
-> Identity LaunchOptions
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (FileBrowserControl -> Identity FileBrowserControl)
-> LaunchControls -> Identity LaunchControls
Lens' LaunchControls FileBrowserControl
fileBrowser ((FileBrowserControl -> Identity FileBrowserControl)
-> LaunchControls -> Identity LaunchControls)
-> ((Maybe FilePath -> Identity (Maybe FilePath))
-> FileBrowserControl -> Identity FileBrowserControl)
-> (Maybe FilePath -> Identity (Maybe FilePath))
-> LaunchControls
-> Identity LaunchControls
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Maybe FilePath -> Identity (Maybe FilePath))
-> FileBrowserControl -> Identity FileBrowserControl
Lens' FileBrowserControl (Maybe FilePath)
maybeSelectedFile ((Maybe FilePath -> Identity (Maybe FilePath))
-> AppState -> Identity AppState)
-> Maybe FilePath -> EventM Name AppState ()
forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= Maybe FilePath
maybeSingleFile
EventM Name AppState ()
closeModal
(Bool, BrickEvent Name AppEvent)
_ -> () -> EventM Name AppState ()
forall a. a -> EventM Name AppState a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
where
closeModal :: EventM Name AppState ()
closeModal = LensLike'
(Zoomed (EventM Name LaunchOptions) ()) AppState LaunchOptions
-> EventM Name LaunchOptions () -> EventM Name AppState ()
forall c.
LensLike'
(Zoomed (EventM Name LaunchOptions) c) AppState LaunchOptions
-> EventM Name LaunchOptions c -> EventM Name AppState c
forall (m :: * -> *) (n :: * -> *) s t c.
Zoom m n s t =>
LensLike' (Zoomed m c) t s -> m c -> n c
Brick.zoom ((UIState -> Focusing (StateT (EventState Name) IO) () UIState)
-> AppState -> Focusing (StateT (EventState Name) IO) () AppState
Lens' AppState UIState
uiState ((UIState -> Focusing (StateT (EventState Name) IO) () UIState)
-> AppState -> Focusing (StateT (EventState Name) IO) () AppState)
-> ((LaunchOptions
-> Focusing (StateT (EventState Name) IO) () LaunchOptions)
-> UIState -> Focusing (StateT (EventState Name) IO) () UIState)
-> (LaunchOptions
-> Focusing (StateT (EventState Name) IO) () LaunchOptions)
-> AppState
-> Focusing (StateT (EventState Name) IO) () AppState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (LaunchOptions
-> Focusing (StateT (EventState Name) IO) () LaunchOptions)
-> UIState -> Focusing (StateT (EventState Name) IO) () UIState
Lens' UIState LaunchOptions
uiLaunchConfig) (EventM Name LaunchOptions () -> EventM Name AppState ())
-> EventM Name LaunchOptions () -> EventM Name AppState ()
forall a b. (a -> b) -> a -> b
$ do
(LaunchControls -> Identity LaunchControls)
-> LaunchOptions -> Identity LaunchOptions
Lens' LaunchOptions LaunchControls
controls ((LaunchControls -> Identity LaunchControls)
-> LaunchOptions -> Identity LaunchOptions)
-> ((Bool -> Identity Bool)
-> LaunchControls -> Identity LaunchControls)
-> (Bool -> Identity Bool)
-> LaunchOptions
-> Identity LaunchOptions
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (FileBrowserControl -> Identity FileBrowserControl)
-> LaunchControls -> Identity LaunchControls
Lens' LaunchControls FileBrowserControl
fileBrowser ((FileBrowserControl -> Identity FileBrowserControl)
-> LaunchControls -> Identity LaunchControls)
-> ((Bool -> Identity Bool)
-> FileBrowserControl -> Identity FileBrowserControl)
-> (Bool -> Identity Bool)
-> LaunchControls
-> Identity LaunchControls
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Bool -> Identity Bool)
-> FileBrowserControl -> Identity FileBrowserControl
Lens' FileBrowserControl Bool
fbIsDisplayed ((Bool -> Identity Bool)
-> LaunchOptions -> Identity LaunchOptions)
-> Bool -> EventM Name LaunchOptions ()
forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= Bool
False
EventM Name LaunchOptions ()
cacheValidatedInputs
handleLaunchOptionsEvent ::
ScenarioInfoPair ->
BrickEvent Name AppEvent ->
EventM Name AppState ()
handleLaunchOptionsEvent :: ScenarioInfoPair
-> BrickEvent Name AppEvent -> EventM Name AppState ()
handleLaunchOptionsEvent ScenarioInfoPair
siPair = \case
Key Key
V.KBackTab ->
(UIState -> Identity UIState) -> AppState -> Identity AppState
Lens' AppState UIState
uiState ((UIState -> Identity UIState) -> AppState -> Identity AppState)
-> ((FocusRing Name -> Identity (FocusRing Name))
-> UIState -> Identity UIState)
-> (FocusRing Name -> Identity (FocusRing Name))
-> AppState
-> Identity AppState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (LaunchOptions -> Identity LaunchOptions)
-> UIState -> Identity UIState
Lens' UIState LaunchOptions
uiLaunchConfig ((LaunchOptions -> Identity LaunchOptions)
-> UIState -> Identity UIState)
-> ((FocusRing Name -> Identity (FocusRing Name))
-> LaunchOptions -> Identity LaunchOptions)
-> (FocusRing Name -> Identity (FocusRing Name))
-> UIState
-> Identity UIState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (LaunchControls -> Identity LaunchControls)
-> LaunchOptions -> Identity LaunchOptions
Lens' LaunchOptions LaunchControls
controls ((LaunchControls -> Identity LaunchControls)
-> LaunchOptions -> Identity LaunchOptions)
-> ((FocusRing Name -> Identity (FocusRing Name))
-> LaunchControls -> Identity LaunchControls)
-> (FocusRing Name -> Identity (FocusRing Name))
-> LaunchOptions
-> Identity LaunchOptions
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (FocusRing Name -> Identity (FocusRing Name))
-> LaunchControls -> Identity LaunchControls
Lens' LaunchControls (FocusRing Name)
scenarioConfigFocusRing ((FocusRing Name -> Identity (FocusRing Name))
-> AppState -> Identity AppState)
-> (FocusRing Name -> FocusRing Name) -> EventM Name AppState ()
forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> (a -> b) -> m ()
%= FocusRing Name -> FocusRing Name
forall n. FocusRing n -> FocusRing n
focusPrev
Key Key
V.KUp ->
(UIState -> Identity UIState) -> AppState -> Identity AppState
Lens' AppState UIState
uiState ((UIState -> Identity UIState) -> AppState -> Identity AppState)
-> ((FocusRing Name -> Identity (FocusRing Name))
-> UIState -> Identity UIState)
-> (FocusRing Name -> Identity (FocusRing Name))
-> AppState
-> Identity AppState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (LaunchOptions -> Identity LaunchOptions)
-> UIState -> Identity UIState
Lens' UIState LaunchOptions
uiLaunchConfig ((LaunchOptions -> Identity LaunchOptions)
-> UIState -> Identity UIState)
-> ((FocusRing Name -> Identity (FocusRing Name))
-> LaunchOptions -> Identity LaunchOptions)
-> (FocusRing Name -> Identity (FocusRing Name))
-> UIState
-> Identity UIState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (LaunchControls -> Identity LaunchControls)
-> LaunchOptions -> Identity LaunchOptions
Lens' LaunchOptions LaunchControls
controls ((LaunchControls -> Identity LaunchControls)
-> LaunchOptions -> Identity LaunchOptions)
-> ((FocusRing Name -> Identity (FocusRing Name))
-> LaunchControls -> Identity LaunchControls)
-> (FocusRing Name -> Identity (FocusRing Name))
-> LaunchOptions
-> Identity LaunchOptions
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (FocusRing Name -> Identity (FocusRing Name))
-> LaunchControls -> Identity LaunchControls
Lens' LaunchControls (FocusRing Name)
scenarioConfigFocusRing ((FocusRing Name -> Identity (FocusRing Name))
-> AppState -> Identity AppState)
-> (FocusRing Name -> FocusRing Name) -> EventM Name AppState ()
forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> (a -> b) -> m ()
%= FocusRing Name -> FocusRing Name
forall n. FocusRing n -> FocusRing n
focusPrev
CharKey Char
'\t' ->
(UIState -> Identity UIState) -> AppState -> Identity AppState
Lens' AppState UIState
uiState ((UIState -> Identity UIState) -> AppState -> Identity AppState)
-> ((FocusRing Name -> Identity (FocusRing Name))
-> UIState -> Identity UIState)
-> (FocusRing Name -> Identity (FocusRing Name))
-> AppState
-> Identity AppState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (LaunchOptions -> Identity LaunchOptions)
-> UIState -> Identity UIState
Lens' UIState LaunchOptions
uiLaunchConfig ((LaunchOptions -> Identity LaunchOptions)
-> UIState -> Identity UIState)
-> ((FocusRing Name -> Identity (FocusRing Name))
-> LaunchOptions -> Identity LaunchOptions)
-> (FocusRing Name -> Identity (FocusRing Name))
-> UIState
-> Identity UIState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (LaunchControls -> Identity LaunchControls)
-> LaunchOptions -> Identity LaunchOptions
Lens' LaunchOptions LaunchControls
controls ((LaunchControls -> Identity LaunchControls)
-> LaunchOptions -> Identity LaunchOptions)
-> ((FocusRing Name -> Identity (FocusRing Name))
-> LaunchControls -> Identity LaunchControls)
-> (FocusRing Name -> Identity (FocusRing Name))
-> LaunchOptions
-> Identity LaunchOptions
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (FocusRing Name -> Identity (FocusRing Name))
-> LaunchControls -> Identity LaunchControls
Lens' LaunchControls (FocusRing Name)
scenarioConfigFocusRing ((FocusRing Name -> Identity (FocusRing Name))
-> AppState -> Identity AppState)
-> (FocusRing Name -> FocusRing Name) -> EventM Name AppState ()
forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> (a -> b) -> m ()
%= FocusRing Name -> FocusRing Name
forall n. FocusRing n -> FocusRing n
focusNext
Key Key
V.KDown ->
(UIState -> Identity UIState) -> AppState -> Identity AppState
Lens' AppState UIState
uiState ((UIState -> Identity UIState) -> AppState -> Identity AppState)
-> ((FocusRing Name -> Identity (FocusRing Name))
-> UIState -> Identity UIState)
-> (FocusRing Name -> Identity (FocusRing Name))
-> AppState
-> Identity AppState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (LaunchOptions -> Identity LaunchOptions)
-> UIState -> Identity UIState
Lens' UIState LaunchOptions
uiLaunchConfig ((LaunchOptions -> Identity LaunchOptions)
-> UIState -> Identity UIState)
-> ((FocusRing Name -> Identity (FocusRing Name))
-> LaunchOptions -> Identity LaunchOptions)
-> (FocusRing Name -> Identity (FocusRing Name))
-> UIState
-> Identity UIState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (LaunchControls -> Identity LaunchControls)
-> LaunchOptions -> Identity LaunchOptions
Lens' LaunchOptions LaunchControls
controls ((LaunchControls -> Identity LaunchControls)
-> LaunchOptions -> Identity LaunchOptions)
-> ((FocusRing Name -> Identity (FocusRing Name))
-> LaunchControls -> Identity LaunchControls)
-> (FocusRing Name -> Identity (FocusRing Name))
-> LaunchOptions
-> Identity LaunchOptions
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (FocusRing Name -> Identity (FocusRing Name))
-> LaunchControls -> Identity LaunchControls
Lens' LaunchControls (FocusRing Name)
scenarioConfigFocusRing ((FocusRing Name -> Identity (FocusRing Name))
-> AppState -> Identity AppState)
-> (FocusRing Name -> FocusRing Name) -> EventM Name AppState ()
forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> (a -> b) -> m ()
%= FocusRing Name -> FocusRing Name
forall n. FocusRing n -> FocusRing n
focusNext
MouseDown Name
n Button
_ [Modifier]
_ Location
_ ->
case Name
n of
ScenarioConfigControl (ScenarioConfigPanelControl ScenarioConfigPanelFocusable
x) -> do
(UIState -> Identity UIState) -> AppState -> Identity AppState
Lens' AppState UIState
uiState ((UIState -> Identity UIState) -> AppState -> Identity AppState)
-> ((FocusRing Name -> Identity (FocusRing Name))
-> UIState -> Identity UIState)
-> (FocusRing Name -> Identity (FocusRing Name))
-> AppState
-> Identity AppState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (LaunchOptions -> Identity LaunchOptions)
-> UIState -> Identity UIState
Lens' UIState LaunchOptions
uiLaunchConfig ((LaunchOptions -> Identity LaunchOptions)
-> UIState -> Identity UIState)
-> ((FocusRing Name -> Identity (FocusRing Name))
-> LaunchOptions -> Identity LaunchOptions)
-> (FocusRing Name -> Identity (FocusRing Name))
-> UIState
-> Identity UIState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (LaunchControls -> Identity LaunchControls)
-> LaunchOptions -> Identity LaunchOptions
Lens' LaunchOptions LaunchControls
controls ((LaunchControls -> Identity LaunchControls)
-> LaunchOptions -> Identity LaunchOptions)
-> ((FocusRing Name -> Identity (FocusRing Name))
-> LaunchControls -> Identity LaunchControls)
-> (FocusRing Name -> Identity (FocusRing Name))
-> LaunchOptions
-> Identity LaunchOptions
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (FocusRing Name -> Identity (FocusRing Name))
-> LaunchControls -> Identity LaunchControls
Lens' LaunchControls (FocusRing Name)
scenarioConfigFocusRing ((FocusRing Name -> Identity (FocusRing Name))
-> AppState -> Identity AppState)
-> (FocusRing Name -> FocusRing Name) -> EventM Name AppState ()
forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> (a -> b) -> m ()
%= Name -> FocusRing Name -> FocusRing Name
forall n. Eq n => n -> FocusRing n -> FocusRing n
focusSetCurrent Name
n
ScenarioConfigPanelFocusable -> EventM Name AppState ()
activateFocusedControl ScenarioConfigPanelFocusable
x
Name
_ -> () -> EventM Name AppState ()
forall a. a -> EventM Name AppState a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
CharKey Char
' ' -> EventM Name AppState ()
activateControl
Key Key
V.KEnter -> EventM Name AppState ()
activateControl
Key Key
V.KEsc -> EventM Name AppState ()
closeModal
CharKey Char
'q' -> EventM Name AppState ()
closeModal
ControlChar Char
'q' -> EventM Name AppState ()
closeModal
BrickEvent Name AppEvent
ev -> do
FocusRing Name
fr <- Getting (FocusRing Name) AppState (FocusRing Name)
-> EventM Name AppState (FocusRing Name)
forall s (m :: * -> *) a. MonadState s m => Getting a s a -> m a
use (Getting (FocusRing Name) AppState (FocusRing Name)
-> EventM Name AppState (FocusRing Name))
-> Getting (FocusRing Name) AppState (FocusRing Name)
-> EventM Name AppState (FocusRing Name)
forall a b. (a -> b) -> a -> b
$ (UIState -> Const (FocusRing Name) UIState)
-> AppState -> Const (FocusRing Name) AppState
Lens' AppState UIState
uiState ((UIState -> Const (FocusRing Name) UIState)
-> AppState -> Const (FocusRing Name) AppState)
-> ((FocusRing Name -> Const (FocusRing Name) (FocusRing Name))
-> UIState -> Const (FocusRing Name) UIState)
-> Getting (FocusRing Name) AppState (FocusRing Name)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (LaunchOptions -> Const (FocusRing Name) LaunchOptions)
-> UIState -> Const (FocusRing Name) UIState
Lens' UIState LaunchOptions
uiLaunchConfig ((LaunchOptions -> Const (FocusRing Name) LaunchOptions)
-> UIState -> Const (FocusRing Name) UIState)
-> Getting (FocusRing Name) LaunchOptions (FocusRing Name)
-> (FocusRing Name -> Const (FocusRing Name) (FocusRing Name))
-> UIState
-> Const (FocusRing Name) UIState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (LaunchControls -> Const (FocusRing Name) LaunchControls)
-> LaunchOptions -> Const (FocusRing Name) LaunchOptions
Lens' LaunchOptions LaunchControls
controls ((LaunchControls -> Const (FocusRing Name) LaunchControls)
-> LaunchOptions -> Const (FocusRing Name) LaunchOptions)
-> ((FocusRing Name -> Const (FocusRing Name) (FocusRing Name))
-> LaunchControls -> Const (FocusRing Name) LaunchControls)
-> Getting (FocusRing Name) LaunchOptions (FocusRing Name)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (FocusRing Name -> Const (FocusRing Name) (FocusRing Name))
-> LaunchControls -> Const (FocusRing Name) LaunchControls
Lens' LaunchControls (FocusRing Name)
scenarioConfigFocusRing
case FocusRing Name -> Maybe Name
forall n. FocusRing n -> Maybe n
focusGetCurrent FocusRing Name
fr of
Just (ScenarioConfigControl (ScenarioConfigPanelControl ScenarioConfigPanelFocusable
SeedSelector)) -> LensLike'
(Zoomed (EventM Name LaunchOptions) ()) AppState LaunchOptions
-> EventM Name LaunchOptions () -> EventM Name AppState ()
forall c.
LensLike'
(Zoomed (EventM Name LaunchOptions) c) AppState LaunchOptions
-> EventM Name LaunchOptions c -> EventM Name AppState c
forall (m :: * -> *) (n :: * -> *) s t c.
Zoom m n s t =>
LensLike' (Zoomed m c) t s -> m c -> n c
Brick.zoom ((UIState -> Focusing (StateT (EventState Name) IO) () UIState)
-> AppState -> Focusing (StateT (EventState Name) IO) () AppState
Lens' AppState UIState
uiState ((UIState -> Focusing (StateT (EventState Name) IO) () UIState)
-> AppState -> Focusing (StateT (EventState Name) IO) () AppState)
-> ((LaunchOptions
-> Focusing (StateT (EventState Name) IO) () LaunchOptions)
-> UIState -> Focusing (StateT (EventState Name) IO) () UIState)
-> (LaunchOptions
-> Focusing (StateT (EventState Name) IO) () LaunchOptions)
-> AppState
-> Focusing (StateT (EventState Name) IO) () AppState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (LaunchOptions
-> Focusing (StateT (EventState Name) IO) () LaunchOptions)
-> UIState -> Focusing (StateT (EventState Name) IO) () UIState
Lens' UIState LaunchOptions
uiLaunchConfig) (EventM Name LaunchOptions () -> EventM Name AppState ())
-> EventM Name LaunchOptions () -> EventM Name AppState ()
forall a b. (a -> b) -> a -> b
$ do
LensLike'
(Zoomed (EventM Name (Editor Text Name)) ())
LaunchOptions
(Editor Text Name)
-> EventM Name (Editor Text Name) ()
-> EventM Name LaunchOptions ()
forall c.
LensLike'
(Zoomed (EventM Name (Editor Text Name)) c)
LaunchOptions
(Editor Text Name)
-> EventM Name (Editor Text Name) c -> EventM Name LaunchOptions c
forall (m :: * -> *) (n :: * -> *) s t c.
Zoom m n s t =>
LensLike' (Zoomed m c) t s -> m c -> n c
Brick.zoom ((LaunchControls
-> Focusing (StateT (EventState Name) IO) () LaunchControls)
-> LaunchOptions
-> Focusing (StateT (EventState Name) IO) () LaunchOptions
Lens' LaunchOptions LaunchControls
controls ((LaunchControls
-> Focusing (StateT (EventState Name) IO) () LaunchControls)
-> LaunchOptions
-> Focusing (StateT (EventState Name) IO) () LaunchOptions)
-> ((Editor Text Name
-> Focusing (StateT (EventState Name) IO) () (Editor Text Name))
-> LaunchControls
-> Focusing (StateT (EventState Name) IO) () LaunchControls)
-> (Editor Text Name
-> Focusing (StateT (EventState Name) IO) () (Editor Text Name))
-> LaunchOptions
-> Focusing (StateT (EventState Name) IO) () LaunchOptions
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Editor Text Name
-> Focusing (StateT (EventState Name) IO) () (Editor Text Name))
-> LaunchControls
-> Focusing (StateT (EventState Name) IO) () LaunchControls
Lens' LaunchControls (Editor Text Name)
seedValueEditor) (BrickEvent Name AppEvent -> EventM Name (Editor Text Name) ()
forall n t e.
(Eq n, DecodeUtf8 t, Eq t, GenericTextZipper t) =>
BrickEvent n e -> EventM n (Editor t n) ()
handleEditorEvent BrickEvent Name AppEvent
ev)
EventM Name LaunchOptions ()
cacheValidatedSeedInput
Maybe Name
_ -> () -> EventM Name AppState ()
forall a. a -> EventM Name AppState a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
where
activateControl :: EventM Name AppState ()
activateControl = do
FocusRing Name
fr <- Getting (FocusRing Name) AppState (FocusRing Name)
-> EventM Name AppState (FocusRing Name)
forall s (m :: * -> *) a. MonadState s m => Getting a s a -> m a
use (Getting (FocusRing Name) AppState (FocusRing Name)
-> EventM Name AppState (FocusRing Name))
-> Getting (FocusRing Name) AppState (FocusRing Name)
-> EventM Name AppState (FocusRing Name)
forall a b. (a -> b) -> a -> b
$ (UIState -> Const (FocusRing Name) UIState)
-> AppState -> Const (FocusRing Name) AppState
Lens' AppState UIState
uiState ((UIState -> Const (FocusRing Name) UIState)
-> AppState -> Const (FocusRing Name) AppState)
-> ((FocusRing Name -> Const (FocusRing Name) (FocusRing Name))
-> UIState -> Const (FocusRing Name) UIState)
-> Getting (FocusRing Name) AppState (FocusRing Name)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (LaunchOptions -> Const (FocusRing Name) LaunchOptions)
-> UIState -> Const (FocusRing Name) UIState
Lens' UIState LaunchOptions
uiLaunchConfig ((LaunchOptions -> Const (FocusRing Name) LaunchOptions)
-> UIState -> Const (FocusRing Name) UIState)
-> Getting (FocusRing Name) LaunchOptions (FocusRing Name)
-> (FocusRing Name -> Const (FocusRing Name) (FocusRing Name))
-> UIState
-> Const (FocusRing Name) UIState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (LaunchControls -> Const (FocusRing Name) LaunchControls)
-> LaunchOptions -> Const (FocusRing Name) LaunchOptions
Lens' LaunchOptions LaunchControls
controls ((LaunchControls -> Const (FocusRing Name) LaunchControls)
-> LaunchOptions -> Const (FocusRing Name) LaunchOptions)
-> ((FocusRing Name -> Const (FocusRing Name) (FocusRing Name))
-> LaunchControls -> Const (FocusRing Name) LaunchControls)
-> Getting (FocusRing Name) LaunchOptions (FocusRing Name)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (FocusRing Name -> Const (FocusRing Name) (FocusRing Name))
-> LaunchControls -> Const (FocusRing Name) LaunchControls
Lens' LaunchControls (FocusRing Name)
scenarioConfigFocusRing
case FocusRing Name -> Maybe Name
forall n. FocusRing n -> Maybe n
focusGetCurrent FocusRing Name
fr of
Just (ScenarioConfigControl (ScenarioConfigPanelControl ScenarioConfigPanelFocusable
item)) ->
ScenarioConfigPanelFocusable -> EventM Name AppState ()
activateFocusedControl ScenarioConfigPanelFocusable
item
Maybe Name
_ -> () -> EventM Name AppState ()
forall a. a -> EventM Name AppState a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
activateFocusedControl :: ScenarioConfigPanelFocusable -> EventM Name AppState ()
activateFocusedControl ScenarioConfigPanelFocusable
item = case ScenarioConfigPanelFocusable
item of
ScenarioConfigPanelFocusable
SeedSelector -> () -> EventM Name AppState ()
forall a. a -> EventM Name AppState a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
ScenarioConfigPanelFocusable
ScriptSelector -> LensLike'
(Zoomed (EventM Name FileBrowserControl) ())
AppState
FileBrowserControl
-> EventM Name FileBrowserControl () -> EventM Name AppState ()
forall c.
LensLike'
(Zoomed (EventM Name FileBrowserControl) c)
AppState
FileBrowserControl
-> EventM Name FileBrowserControl c -> EventM Name AppState c
forall (m :: * -> *) (n :: * -> *) s t c.
Zoom m n s t =>
LensLike' (Zoomed m c) t s -> m c -> n c
Brick.zoom ((UIState -> Zoomed (EventM Name FileBrowserControl) () UIState)
-> AppState -> Zoomed (EventM Name FileBrowserControl) () AppState
Lens' AppState UIState
uiState ((UIState -> Zoomed (EventM Name FileBrowserControl) () UIState)
-> AppState -> Zoomed (EventM Name FileBrowserControl) () AppState)
-> ((FileBrowserControl
-> Zoomed (EventM Name FileBrowserControl) () FileBrowserControl)
-> UIState -> Zoomed (EventM Name FileBrowserControl) () UIState)
-> LensLike'
(Zoomed (EventM Name FileBrowserControl) ())
AppState
FileBrowserControl
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (LaunchOptions
-> Zoomed (EventM Name FileBrowserControl) () LaunchOptions)
-> UIState -> Zoomed (EventM Name FileBrowserControl) () UIState
Lens' UIState LaunchOptions
uiLaunchConfig ((LaunchOptions
-> Zoomed (EventM Name FileBrowserControl) () LaunchOptions)
-> UIState -> Zoomed (EventM Name FileBrowserControl) () UIState)
-> ((FileBrowserControl
-> Zoomed (EventM Name FileBrowserControl) () FileBrowserControl)
-> LaunchOptions
-> Zoomed (EventM Name FileBrowserControl) () LaunchOptions)
-> (FileBrowserControl
-> Zoomed (EventM Name FileBrowserControl) () FileBrowserControl)
-> UIState
-> Zoomed (EventM Name FileBrowserControl) () UIState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (LaunchControls
-> Zoomed (EventM Name FileBrowserControl) () LaunchControls)
-> LaunchOptions
-> Zoomed (EventM Name FileBrowserControl) () LaunchOptions
Lens' LaunchOptions LaunchControls
controls ((LaunchControls
-> Zoomed (EventM Name FileBrowserControl) () LaunchControls)
-> LaunchOptions
-> Zoomed (EventM Name FileBrowserControl) () LaunchOptions)
-> ((FileBrowserControl
-> Zoomed (EventM Name FileBrowserControl) () FileBrowserControl)
-> LaunchControls
-> Zoomed (EventM Name FileBrowserControl) () LaunchControls)
-> (FileBrowserControl
-> Zoomed (EventM Name FileBrowserControl) () FileBrowserControl)
-> LaunchOptions
-> Zoomed (EventM Name FileBrowserControl) () LaunchOptions
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (FileBrowserControl
-> Zoomed (EventM Name FileBrowserControl) () FileBrowserControl)
-> LaunchControls
-> Zoomed (EventM Name FileBrowserControl) () LaunchControls
Lens' LaunchControls FileBrowserControl
fileBrowser) (EventM Name FileBrowserControl () -> EventM Name AppState ())
-> EventM Name FileBrowserControl () -> EventM Name AppState ()
forall a b. (a -> b) -> a -> b
$ do
Maybe FilePath
maybeSingleFile <- Getting (Maybe FilePath) FileBrowserControl (Maybe FilePath)
-> EventM Name FileBrowserControl (Maybe FilePath)
forall s (m :: * -> *) a. MonadState s m => Getting a s a -> m a
use Getting (Maybe FilePath) FileBrowserControl (Maybe FilePath)
Lens' FileBrowserControl (Maybe FilePath)
maybeSelectedFile
FileBrowser Name
configuredFB <- Maybe FilePath -> EventM Name FileBrowserControl (FileBrowser Name)
forall (m :: * -> *).
MonadIO m =>
Maybe FilePath -> m (FileBrowser Name)
initFileBrowserWidget Maybe FilePath
maybeSingleFile
(FileBrowser Name -> Identity (FileBrowser Name))
-> FileBrowserControl -> Identity FileBrowserControl
Lens' FileBrowserControl (FileBrowser Name)
fbWidget ((FileBrowser Name -> Identity (FileBrowser Name))
-> FileBrowserControl -> Identity FileBrowserControl)
-> FileBrowser Name -> EventM Name FileBrowserControl ()
forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= FileBrowser Name
configuredFB
(Bool -> Identity Bool)
-> FileBrowserControl -> Identity FileBrowserControl
Lens' FileBrowserControl Bool
fbIsDisplayed ((Bool -> Identity Bool)
-> FileBrowserControl -> Identity FileBrowserControl)
-> Bool -> EventM Name FileBrowserControl ()
forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= Bool
True
ScenarioConfigPanelFocusable
StartGameButton -> do
EditingLaunchParams
params <- Getting EditingLaunchParams AppState EditingLaunchParams
-> EventM Name AppState EditingLaunchParams
forall s (m :: * -> *) a. MonadState s m => Getting a s a -> m a
use (Getting EditingLaunchParams AppState EditingLaunchParams
-> EventM Name AppState EditingLaunchParams)
-> Getting EditingLaunchParams AppState EditingLaunchParams
-> EventM Name AppState EditingLaunchParams
forall a b. (a -> b) -> a -> b
$ (UIState -> Const EditingLaunchParams UIState)
-> AppState -> Const EditingLaunchParams AppState
Lens' AppState UIState
uiState ((UIState -> Const EditingLaunchParams UIState)
-> AppState -> Const EditingLaunchParams AppState)
-> ((EditingLaunchParams
-> Const EditingLaunchParams EditingLaunchParams)
-> UIState -> Const EditingLaunchParams UIState)
-> Getting EditingLaunchParams AppState EditingLaunchParams
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (LaunchOptions -> Const EditingLaunchParams LaunchOptions)
-> UIState -> Const EditingLaunchParams UIState
Lens' UIState LaunchOptions
uiLaunchConfig ((LaunchOptions -> Const EditingLaunchParams LaunchOptions)
-> UIState -> Const EditingLaunchParams UIState)
-> Getting EditingLaunchParams LaunchOptions EditingLaunchParams
-> (EditingLaunchParams
-> Const EditingLaunchParams EditingLaunchParams)
-> UIState
-> Const EditingLaunchParams UIState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Getting EditingLaunchParams LaunchOptions EditingLaunchParams
Lens' LaunchOptions EditingLaunchParams
editingParams
let eitherLaunchParams :: Either Text ValidatedLaunchParams
eitherLaunchParams = EditingLaunchParams -> Either Text ValidatedLaunchParams
toValidatedParams EditingLaunchParams
params
Either Text ValidatedLaunchParams
-> (ValidatedLaunchParams -> EventM Name AppState ())
-> EventM Name AppState ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ Either Text ValidatedLaunchParams
eitherLaunchParams ((ValidatedLaunchParams -> EventM Name AppState ())
-> EventM Name AppState ())
-> (ValidatedLaunchParams -> EventM Name AppState ())
-> EventM Name AppState ()
forall a b. (a -> b) -> a -> b
$ \ValidatedLaunchParams
launchParams -> do
EventM Name AppState ()
closeModal
ScenarioInfoPair
-> ValidatedLaunchParams -> EventM Name AppState ()
forall (m :: * -> *).
(MonadIO m, MonadState AppState m) =>
ScenarioInfoPair -> ValidatedLaunchParams -> m ()
startGameWithSeed ScenarioInfoPair
siPair ValidatedLaunchParams
launchParams
closeModal :: EventM Name AppState ()
closeModal = (UIState -> Identity UIState) -> AppState -> Identity AppState
Lens' AppState UIState
uiState ((UIState -> Identity UIState) -> AppState -> Identity AppState)
-> ((Maybe ScenarioInfoPair -> Identity (Maybe ScenarioInfoPair))
-> UIState -> Identity UIState)
-> (Maybe ScenarioInfoPair -> Identity (Maybe ScenarioInfoPair))
-> AppState
-> Identity AppState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (LaunchOptions -> Identity LaunchOptions)
-> UIState -> Identity UIState
Lens' UIState LaunchOptions
uiLaunchConfig ((LaunchOptions -> Identity LaunchOptions)
-> UIState -> Identity UIState)
-> ((Maybe ScenarioInfoPair -> Identity (Maybe ScenarioInfoPair))
-> LaunchOptions -> Identity LaunchOptions)
-> (Maybe ScenarioInfoPair -> Identity (Maybe ScenarioInfoPair))
-> UIState
-> Identity UIState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (LaunchControls -> Identity LaunchControls)
-> LaunchOptions -> Identity LaunchOptions
Lens' LaunchOptions LaunchControls
controls ((LaunchControls -> Identity LaunchControls)
-> LaunchOptions -> Identity LaunchOptions)
-> ((Maybe ScenarioInfoPair -> Identity (Maybe ScenarioInfoPair))
-> LaunchControls -> Identity LaunchControls)
-> (Maybe ScenarioInfoPair -> Identity (Maybe ScenarioInfoPair))
-> LaunchOptions
-> Identity LaunchOptions
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Maybe ScenarioInfoPair -> Identity (Maybe ScenarioInfoPair))
-> LaunchControls -> Identity LaunchControls
Lens' LaunchControls (Maybe ScenarioInfoPair)
isDisplayedFor ((Maybe ScenarioInfoPair -> Identity (Maybe ScenarioInfoPair))
-> AppState -> Identity AppState)
-> Maybe ScenarioInfoPair -> EventM Name AppState ()
forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= Maybe ScenarioInfoPair
forall a. Maybe a
Nothing