-
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
13 changed files
with
455 additions
and
40 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
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,74 @@ | ||
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 (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 | ||
|
||
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 = uiState . uiLaunchConfig . controls . fileBrowser . fbIsDisplayed .= False | ||
|
||
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)) -> | ||
Brick.zoom (uiState . uiLaunchConfig . controls . seedValueEditor) (handleEditorEvent ev) | ||
_ -> 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 | ||
launchControls <- use $ uiState . uiLaunchConfig . controls | ||
eitherLaunchParams <- liftIO $ toValidatedParms launchControls | ||
case eitherLaunchParams of | ||
Left errMsg -> return () -- TODO FIXME | ||
Right 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,44 @@ | ||
{-# 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 | ||
|
||
-- | UI elements to configure scenario launch options | ||
data LaunchOptions = LaunchOptions | ||
{ _controls :: LaunchControls | ||
, _validatedParams :: ValidatedLaunchParms | ||
} | ||
|
||
makeLenses ''LaunchOptions |
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,57 @@ | ||
{-# LANGUAGE OverloadedStrings #-} | ||
|
||
module Swarm.TUI.Launch.Prep where | ||
|
||
import Brick.Focus qualified as Focus | ||
import Brick.Widgets.Edit | ||
import Brick.Widgets.FileBrowser qualified as FB | ||
import Control.Arrow (left) | ||
import Control.Monad.Trans.Except (ExceptT (..), except, runExceptT) | ||
import Data.Maybe (listToMaybe) | ||
import Data.Text (Text) | ||
import Data.Text qualified as T | ||
import Swarm.Game.State (parseCodeFile) | ||
import Swarm.TUI.Launch.Model | ||
import Swarm.TUI.Model.Name | ||
import Swarm.Util (listEnums) | ||
import Text.Read (readEither) | ||
|
||
toValidatedParms :: LaunchControls -> IO (Either Text ValidatedLaunchParms) | ||
toValidatedParms (LaunchControls (FileBrowserControl fb _) seedEditor _ _) = runExceptT $ do | ||
maybeParsedCode <- case maybeSelectedFile of | ||
Nothing -> return Nothing | ||
Just filePath -> do | ||
code <- ExceptT $ parseCodeFile filePath | ||
return $ Just code | ||
|
||
maybeSeed <- | ||
if T.null seedFieldText | ||
then return Nothing | ||
else do | ||
val <- except $ left T.pack $ readEither $ T.unpack seedFieldText | ||
return $ Just val | ||
|
||
return $ ValidatedLaunchParms maybeSeed maybeParsedCode | ||
where | ||
seedFieldText = mconcat $ getEditContents seedEditor | ||
maybeSelectedFile = | ||
FB.fileInfoFilePath | ||
<$> listToMaybe (FB.fileBrowserSelection fb) | ||
|
||
initConfigPanel :: IO LaunchOptions | ||
initConfigPanel = do | ||
fb <- | ||
FB.newFileBrowser | ||
FB.selectNonDirectories | ||
-- (const False) | ||
(ScenarioConfigControl $ ScenarioConfigPanelControl ScriptSelector) | ||
Nothing | ||
let configuredFB = FB.setFileBrowserEntryFilter (Just $ FB.fileExtensionMatch "sw") fb | ||
return $ LaunchOptions (LaunchControls (FileBrowserControl configuredFB False) myForm ring Nothing) (ValidatedLaunchParms Nothing Nothing) | ||
where | ||
myForm = | ||
editorText | ||
(ScenarioConfigControl $ ScenarioConfigPanelControl SeedSelector) | ||
(Just 1) | ||
"" | ||
ring = Focus.focusRing $ map (ScenarioConfigControl . ScenarioConfigPanelControl) listEnums |
Oops, something went wrong.