-
Notifications
You must be signed in to change notification settings - Fork 52
Commit
This commit does not belong to any branch on this repository, and may belong to a fork outside of the repository.
Scenario launch configuration dialog
Towards #358
- Loading branch information
Showing
14 changed files
with
532 additions
and
55 deletions.
There are no files selected for viewing
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,80 @@ | ||
module Swarm.TUI.Launch.Controller where | ||
|
||
import Brick hiding (Direction, Location) | ||
import Brick.Focus | ||
import Brick.Widgets.Edit (handleEditorEvent) | ||
import Brick.Widgets.FileBrowser | ||
import Control.Lens | ||
import Control.Monad.Except (forM_, liftIO) | ||
import Graphics.Vty qualified as V | ||
import Swarm.Game.ScenarioInfo | ||
import Swarm.TUI.Controller.Util | ||
import Swarm.TUI.Launch.Model | ||
import Swarm.TUI.Launch.Prep (toValidatedParms) | ||
import Swarm.TUI.Model | ||
import Swarm.TUI.Model.Name | ||
import Swarm.TUI.Model.StateUpdate | ||
import Swarm.TUI.Model.UI | ||
|
||
cacheValidatedInputs :: EventM Name AppState () | ||
cacheValidatedInputs = do | ||
launchControls <- use $ uiState . uiLaunchConfig . controls | ||
eitherLaunchParams <- liftIO $ toValidatedParms launchControls | ||
uiState . uiLaunchConfig . validatedParams .= eitherLaunchParams | ||
|
||
handleFBEvent :: | ||
BrickEvent Name AppEvent -> | ||
EventM Name AppState () | ||
handleFBEvent = \case | ||
Key V.KEsc -> closeModal | ||
CharKey 'q' -> closeModal | ||
ControlChar 'q' -> closeModal | ||
VtyEvent e -> | ||
Brick.zoom (uiState . uiLaunchConfig . controls . fileBrowser . fbWidget) (handleFileBrowserEvent e) | ||
_ -> return () | ||
where | ||
closeModal = do | ||
uiState . uiLaunchConfig . controls . fileBrowser . fbIsDisplayed .= False | ||
cacheValidatedInputs | ||
|
||
handleLaunchOptionsEvent :: | ||
ScenarioInfoPair -> | ||
BrickEvent Name AppEvent -> | ||
EventM Name AppState () | ||
handleLaunchOptionsEvent siPair = \case | ||
Key V.KBackTab -> | ||
uiState . uiLaunchConfig . controls . scenarioConfigFocusRing %= focusPrev | ||
Key V.KUp -> | ||
uiState . uiLaunchConfig . controls . scenarioConfigFocusRing %= focusPrev | ||
CharKey '\t' -> | ||
uiState . uiLaunchConfig . controls . scenarioConfigFocusRing %= focusNext | ||
Key V.KDown -> | ||
uiState . uiLaunchConfig . controls . scenarioConfigFocusRing %= focusNext | ||
CharKey ' ' -> activateControl | ||
Key V.KEnter -> activateControl | ||
Key V.KEsc -> closeModal | ||
CharKey 'q' -> closeModal | ||
ControlChar 'q' -> closeModal | ||
ev -> do | ||
fr <- use $ uiState . uiLaunchConfig . controls . scenarioConfigFocusRing | ||
case focusGetCurrent fr of | ||
Just (ScenarioConfigControl (ScenarioConfigPanelControl SeedSelector)) -> do | ||
Brick.zoom (uiState . uiLaunchConfig . controls . seedValueEditor) (handleEditorEvent ev) | ||
cacheValidatedInputs | ||
_ -> return () | ||
where | ||
activateControl = do | ||
fr <- use $ uiState . uiLaunchConfig . controls . scenarioConfigFocusRing | ||
case focusGetCurrent fr of | ||
Just (ScenarioConfigControl (ScenarioConfigPanelControl item)) -> case item of | ||
SeedSelector -> return () | ||
ScriptSelector -> | ||
uiState . uiLaunchConfig . controls . fileBrowser . fbIsDisplayed .= True | ||
StartGameButton -> do | ||
eitherLaunchParams <- use $ uiState . uiLaunchConfig . validatedParams | ||
forM_ eitherLaunchParams $ \launchParams -> do | ||
closeModal | ||
startGameWithSeed siPair launchParams | ||
_ -> return () | ||
|
||
closeModal = uiState . uiLaunchConfig . controls . isDisplayedFor .= Nothing |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,49 @@ | ||
{-# LANGUAGE OverloadedStrings #-} | ||
{-# LANGUAGE TemplateHaskell #-} | ||
|
||
module Swarm.TUI.Launch.Model where | ||
|
||
import Brick.Focus qualified as Focus | ||
import Brick.Widgets.Edit | ||
import Brick.Widgets.FileBrowser qualified as FB | ||
import Control.Lens (makeLenses) | ||
import Data.Text (Text) | ||
import Swarm.Game.ScenarioInfo | ||
import Swarm.Game.State (CodeToRun) | ||
import Swarm.Game.WorldGen (Seed) | ||
import Swarm.TUI.Model.Name | ||
|
||
data ValidatedLaunchParms = ValidatedLaunchParms | ||
{ seedVal :: Maybe Seed | ||
, initialCode :: Maybe CodeToRun | ||
} | ||
|
||
data FileBrowserControl = FileBrowserControl | ||
{ _fbWidget :: FB.FileBrowser Name | ||
, _fbIsDisplayed :: Bool | ||
} | ||
|
||
makeLenses ''FileBrowserControl | ||
|
||
-- | UI elements to configure scenario launch options | ||
data LaunchControls = LaunchControls | ||
{ _fileBrowser :: FileBrowserControl | ||
, _seedValueEditor :: Editor Text Name | ||
, _scenarioConfigFocusRing :: Focus.FocusRing Name | ||
, _isDisplayedFor :: Maybe ScenarioInfoPair | ||
} | ||
|
||
makeLenses ''LaunchControls | ||
|
||
data LaunchFormError = LaunchFormError | ||
{ widget :: ScenarioConfigPanelFocusable | ||
, message :: Text | ||
} | ||
|
||
-- | UI elements to configure scenario launch options | ||
data LaunchOptions = LaunchOptions | ||
{ _controls :: LaunchControls | ||
, _validatedParams :: Either LaunchFormError ValidatedLaunchParms | ||
} | ||
|
||
makeLenses ''LaunchOptions |
Oops, something went wrong.