Skip to content

Commit

Permalink
wip
Browse files Browse the repository at this point in the history
  • Loading branch information
kostmo committed Feb 22, 2023
1 parent 014cc51 commit c96caa6
Show file tree
Hide file tree
Showing 8 changed files with 82 additions and 71 deletions.
4 changes: 2 additions & 2 deletions src/Swarm/TUI/Controller.hs
Original file line number Diff line number Diff line change
Expand Up @@ -74,8 +74,6 @@ import Swarm.Game.Entity hiding (empty)
import Swarm.Game.Location
import Swarm.Game.ResourceLoading (getSwarmHistoryPath)
import Swarm.Game.Robot
import Swarm.TUI.Launch.Controller
import Swarm.TUI.Launch.Model
import Swarm.Game.ScenarioInfo
import Swarm.Game.State
import Swarm.Game.Step (finishGameTick, gameTick)
Expand All @@ -94,6 +92,8 @@ import Swarm.Language.Types
import Swarm.Language.Value (Value (VUnit), prettyValue, stripVResult)
import Swarm.TUI.Controller.Util
import Swarm.TUI.Inventory.Sorting (cycleSortDirection, cycleSortOrder)
import Swarm.TUI.Launch.Controller
import Swarm.TUI.Launch.Model
import Swarm.TUI.List
import Swarm.TUI.Model
import Swarm.TUI.Model.Goal
Expand Down
6 changes: 3 additions & 3 deletions src/Swarm/TUI/Launch/Controller.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,16 +5,16 @@ 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.TUI.Launch.Model
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
import Swarm.TUI.Launch.Prep (toValidatedParms)
import Control.Monad.Except (liftIO)

handleFBEvent ::
BrickEvent Name AppEvent ->
Expand Down
10 changes: 4 additions & 6 deletions src/Swarm/TUI/Launch/Model.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,18 +3,18 @@

module Swarm.TUI.Launch.Model where

import Swarm.Game.WorldGen (Seed)
import Swarm.Game.State (CodeToRun)
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
data ValidatedLaunchParms = ValidatedLaunchParms
{ seedVal :: Maybe Seed
, initialCode :: Maybe CodeToRun
}

Expand All @@ -25,7 +25,6 @@ data FileBrowserControl = FileBrowserControl

makeLenses ''FileBrowserControl


-- | UI elements to configure scenario launch options
data LaunchControls = LaunchControls
{ _fileBrowser :: FileBrowserControl
Expand All @@ -36,7 +35,6 @@ data LaunchControls = LaunchControls

makeLenses ''LaunchControls


-- | UI elements to configure scenario launch options
data LaunchOptions = LaunchOptions
{ _controls :: LaunchControls
Expand Down
33 changes: 17 additions & 16 deletions src/Swarm/TUI/Launch/Prep.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,20 +2,19 @@

module Swarm.TUI.Launch.Prep where

import Swarm.TUI.Launch.Model
import Control.Arrow (left)
import Text.Read (readEither)
import Data.Maybe (listToMaybe)
import Control.Monad.Trans.Except (except, runExceptT, ExceptT (..))
import Brick.Focus qualified as Focus
import Brick.Widgets.Edit
import Swarm.Game.State (parseCodeFile)
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
Expand All @@ -25,17 +24,19 @@ toValidatedParms (LaunchControls (FileBrowserControl fb _) seedEditor _ _) = run
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
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)
where
seedFieldText = mconcat $ getEditContents seedEditor
maybeSelectedFile =
FB.fileInfoFilePath
<$> listToMaybe (FB.fileBrowserSelection fb)

initConfigPanel :: IO LaunchOptions
initConfigPanel = do
Expand Down
89 changes: 51 additions & 38 deletions src/Swarm/TUI/Launch/View.hs
Original file line number Diff line number Diff line change
Expand Up @@ -13,8 +13,8 @@ import Brick.Widgets.FileBrowser qualified as FB
import Control.Exception qualified as E
import Data.Maybe (listToMaybe)
import Data.Text qualified as T
import Swarm.TUI.Launch.Model
import Swarm.TUI.Attr
import Swarm.TUI.Launch.Model
import Swarm.TUI.Model.Name

drawFileBrowser :: FB.FileBrowser Name -> Widget Name
Expand All @@ -26,12 +26,14 @@ drawFileBrowser b =
borderWithLabel (txt "Choose a file") $
FB.renderFileBrowser True b

footerRows = map (hCenter . txt) [
"Up/Down: select"
, "/: search, Ctrl-C or Esc: cancel search"
, "Enter: change directory or select file"
, "Esc: quit"
]
footerRows =
map
(hCenter . txt)
[ "Up/Down: select"
, "/: search, Ctrl-C or Esc: cancel search"
, "Enter: change directory or select file"
, "Esc: quit"
]

help =
padTop (Pad 1) $
Expand All @@ -44,15 +46,17 @@ drawFileBrowser b =
txt $
T.pack $
E.displayException e
] <> footerRows
]
<> footerRows

drawLaunchConfigPanel :: LaunchOptions -> [Widget Name]
drawLaunchConfigPanel (LaunchOptions (LaunchControls (FileBrowserControl fb isFbDisplayed) seedEditor ring _isDisplayedFor) _validatedOptions) =
addFileBrowser [panelWidget]
addFileBrowser [panelWidget]
where
addFileBrowser = if isFbDisplayed
then (drawFileBrowser fb:)
else id
addFileBrowser =
if isFbDisplayed
then (drawFileBrowser fb :)
else id

isFocused x = focusGetCurrent ring == Just (ScenarioConfigControl (ScenarioConfigPanelControl x))

Expand All @@ -64,34 +68,43 @@ drawLaunchConfigPanel (LaunchOptions (LaunchControls (FileBrowserControl fb isFb
mkButton name label = highlightIfFocused name $ str label

seedEntryContent = mconcat $ getEditContents seedEditor
seedEntryWidget = if T.null seedEntryContent && not (isFocused SeedSelector)
then str "<scenario default>"
else hLimit 10 $
overrideAttr E.editFocusedAttr customEditFocusedAttr $
renderEditor (txt . mconcat) (isFocused SeedSelector) seedEditor
seedEntryWidget =
if T.null seedEntryContent && not (isFocused SeedSelector)
then str "<scenario default>"
else
hLimit 10 $
overrideAttr E.editFocusedAttr customEditFocusedAttr $
renderEditor (txt . mconcat) (isFocused SeedSelector) seedEditor

unspecifiedFileMessage = if isFocused ScriptSelector
then "<Hit [Enter] to select>"
else "<none>"
fileEntryWidget = str $
maybe unspecifiedFileMessage FB.fileInfoSanitizedFilename $
listToMaybe $
FB.fileBrowserSelection fb
unspecifiedFileMessage =
if isFocused ScriptSelector
then "<Hit [Enter] to select>"
else "<none>"
fileEntryWidget =
str $
maybe unspecifiedFileMessage FB.fileInfoSanitizedFilename $
listToMaybe $
FB.fileBrowserSelection fb

panelWidget =
centerLayer $
borderWithLabel (str "Configure scenario launch") $
hLimit 50 $ padAll 1 $
vBox
[ padBottom (Pad 1) $ txtWrap "Leaving this field blank will use the default seed for the scenario."
, padBottom (Pad 1) $ padLeft (Pad 2) $ hBox
[ mkButton SeedSelector "Seed: "
, seedEntryWidget
]
, padBottom (Pad 1) $ txtWrap "Selecting a script to be run upon start enables eligibility for code size scoring."
, padBottom (Pad 1) $ padLeft (Pad 2) $ hBox
[ mkButton ScriptSelector "Script: "
, fileEntryWidget
]
, hCenter $ mkButton StartGameButton ">> Launch with these settings <<"
]
hLimit 50 $
padAll 1 $
vBox
[ padBottom (Pad 1) $ txtWrap "Leaving this field blank will use the default seed for the scenario."
, padBottom (Pad 1) $
padLeft (Pad 2) $
hBox
[ mkButton SeedSelector "Seed: "
, seedEntryWidget
]
, padBottom (Pad 1) $ txtWrap "Selecting a script to be run upon start enables eligibility for code size scoring."
, padBottom (Pad 1) $
padLeft (Pad 2) $
hBox
[ mkButton ScriptSelector "Script: "
, fileEntryWidget
]
, hCenter $ mkButton StartGameButton ">> Launch with these settings <<"
]
3 changes: 1 addition & 2 deletions src/Swarm/TUI/Model/StateUpdate.hs
Original file line number Diff line number Diff line change
Expand Up @@ -12,7 +12,6 @@ module Swarm.TUI.Model.StateUpdate (
) where

import Brick.AttrMap (applyAttrMappings)
import Swarm.TUI.Launch.Model (ValidatedLaunchParms (..))
import Control.Applicative ((<|>))
import Control.Lens hiding (from, (<.>))
import Control.Monad.Except
Expand Down Expand Up @@ -42,6 +41,7 @@ import Swarm.Game.ScenarioInfo (
import Swarm.Game.State
import Swarm.TUI.Attr (swarmAttrMap)
import Swarm.TUI.Inventory.Sorting
import Swarm.TUI.Launch.Model (ValidatedLaunchParms (..))
import Swarm.TUI.Model
import Swarm.TUI.Model.Goal (emptyGoalDisplay)
import Swarm.TUI.Model.Repl
Expand Down Expand Up @@ -74,7 +74,6 @@ initAppState AppOpts {..} = do
(startGameWithSeed (scenario, ScenarioInfo path NotStarted NotStarted NotStarted) $ ValidatedLaunchParms userSeed codeToRun)
(AppState gs ui rs)


-- | Load a 'Scenario' and start playing the game.
startGame :: (MonadIO m, MonadState AppState m) => ScenarioInfoPair -> Maybe CodeToRun -> m ()
startGame siPair = startGameWithSeed siPair . ValidatedLaunchParms Nothing
Expand Down
4 changes: 2 additions & 2 deletions src/Swarm/TUI/Model/UI.hs
Original file line number Diff line number Diff line change
Expand Up @@ -62,8 +62,6 @@ import Data.Text qualified as T
import Swarm.Game.Achievement.Attainment
import Swarm.Game.Achievement.Definitions
import Swarm.Game.Achievement.Persistence
import Swarm.TUI.Launch.Model
import Swarm.TUI.Launch.Prep
import Swarm.Game.Failure (SystemFailure)
import Swarm.Game.Failure.Render (prettyFailure)
import Swarm.Game.ResourceLoading (getSwarmHistoryPath, readAppData)
Expand All @@ -73,6 +71,8 @@ import Swarm.Game.ScenarioInfo (
import Swarm.Game.World qualified as W
import Swarm.TUI.Attr (swarmAttrMap)
import Swarm.TUI.Inventory.Sorting
import Swarm.TUI.Launch.Model
import Swarm.TUI.Launch.Prep
import Swarm.TUI.Model.Goal
import Swarm.TUI.Model.Menu
import Swarm.TUI.Model.Name
Expand Down
4 changes: 2 additions & 2 deletions src/Swarm/TUI/View.hs
Original file line number Diff line number Diff line change
Expand Up @@ -81,8 +81,6 @@ import Swarm.Game.Location
import Swarm.Game.Recipe
import Swarm.Game.Robot
import Swarm.Game.Scenario (scenarioAuthor, scenarioDescription, scenarioName, scenarioObjectives)
import Swarm.TUI.Launch.Model
import Swarm.TUI.Launch.View
import Swarm.Game.ScenarioInfo (
ScenarioItem (..),
ScenarioStatus (..),
Expand All @@ -100,6 +98,8 @@ import Swarm.Language.Typecheck (inferConst)
import Swarm.TUI.Attr
import Swarm.TUI.Border
import Swarm.TUI.Inventory.Sorting (renderSortMethod)
import Swarm.TUI.Launch.Model
import Swarm.TUI.Launch.View
import Swarm.TUI.Model
import Swarm.TUI.Model.Goal (goalsContent, hasAnythingToShow)
import Swarm.TUI.Model.Repl
Expand Down

0 comments on commit c96caa6

Please sign in to comment.