mirror of
https://github.com/swarm-game/swarm.git
synced 2025-01-05 23:34:35 +03:00
various documentation improvements (#1439)
formatting, licenses, adding info
This commit is contained in:
parent
da6ad0c874
commit
6345de17d1
@ -6,8 +6,9 @@
|
||||
-- Assess pedagogical soundness of the tutorials.
|
||||
--
|
||||
-- Approach:
|
||||
--
|
||||
-- 1. Obtain a list of all of the tutorial scenarios, in order
|
||||
-- 2. Search their "solution" code for `commands`
|
||||
-- 2. Search their \"solution\" code for `commands`
|
||||
-- 3. "fold" over the tutorial list, noting which tutorial was first to introduce each command
|
||||
module Swarm.Doc.Pedagogy (
|
||||
renderTutorialProgression,
|
||||
|
@ -4,6 +4,8 @@
|
||||
-- SPDX-License-Identifier: BSD-3-Clause
|
||||
--
|
||||
-- Load/save logic for achievements.
|
||||
-- Each achievement is saved to its own file to better
|
||||
-- support forward-compatibility.
|
||||
module Swarm.Game.Achievement.Persistence where
|
||||
|
||||
import Control.Arrow (left)
|
||||
|
@ -35,17 +35,17 @@ data PrerequisiteConfig = PrerequisiteConfig
|
||||
-- explain the broader intention behind potentially multiple
|
||||
-- prerequisites.
|
||||
--
|
||||
-- Set this to option True to display this goal in the "upcoming" section even
|
||||
-- Set this option to 'True' to display this goal in the "upcoming" section even
|
||||
-- if the objective has currently unmet prerequisites.
|
||||
, logic :: Prerequisite ObjectiveLabel
|
||||
-- ^ Boolean expression of dependencies upon other objectives. Variables in this expression
|
||||
-- are the "id"s of other objectives, and become "true" if the corresponding objective is completed.
|
||||
-- The "condition" of the objective at hand shall not be evaluated until its
|
||||
-- prerequisite expression evaluates as True.
|
||||
-- prerequisite expression evaluates as 'True'.
|
||||
--
|
||||
-- Note that the achievement of these objective dependencies is
|
||||
-- persistent; once achieved, they still count even if their "condition"
|
||||
-- might not still hold. The condition is never re-evaluated once True.
|
||||
-- might not still hold. The condition is never re-evaluated once true.
|
||||
}
|
||||
deriving (Eq, Show, Generic, ToJSON)
|
||||
|
||||
@ -115,7 +115,7 @@ objectivePrerequisite :: Lens' Objective (Maybe PrerequisiteConfig)
|
||||
-- This attribute often goes along with an Achievement.
|
||||
objectiveHidden :: Lens' Objective Bool
|
||||
|
||||
-- | An optional Achievement that is to be registered globally
|
||||
-- | An optional achievement that is to be registered globally
|
||||
-- when this objective is completed.
|
||||
objectiveAchievement :: Lens' Objective (Maybe AchievementInfo)
|
||||
|
||||
|
@ -3,7 +3,7 @@
|
||||
-- |
|
||||
-- SPDX-License-Identifier: BSD-3-Clause
|
||||
--
|
||||
-- Validity checking for Objective prerequisites
|
||||
-- Validity checking for 'Objective' prerequisites
|
||||
module Swarm.Game.Scenario.Objective.Validation where
|
||||
|
||||
import Control.Monad (unless)
|
||||
@ -19,9 +19,10 @@ import Swarm.Util (failT, quote)
|
||||
-- | Performs monadic validation before returning
|
||||
-- the "pure" construction of a wrapper record.
|
||||
-- This validation entails:
|
||||
-- 1) Ensuring that all goal references utilized in prerequisites
|
||||
--
|
||||
-- 1. Ensuring that all goal references utilized in prerequisites
|
||||
-- actually exist
|
||||
-- 2) Ensuring that the graph of dependencies is acyclic.
|
||||
-- 2. Ensuring that the graph of dependencies is acyclic.
|
||||
validateObjectives ::
|
||||
MonadFail m =>
|
||||
[Objective] ->
|
||||
|
@ -2,7 +2,10 @@
|
||||
{-# LANGUAGE TemplateHaskell #-}
|
||||
{-# OPTIONS_GHC -Wno-orphans #-}
|
||||
|
||||
-- | Types and records for updating and retrieving
|
||||
-- |
|
||||
-- SPDX-License-Identifier: BSD-3-Clause
|
||||
--
|
||||
-- Types and records for updating and retrieving
|
||||
-- the best scores for a scenario.
|
||||
module Swarm.Game.Scenario.Scoring.Best where
|
||||
|
||||
|
@ -1,5 +1,8 @@
|
||||
-- | Types and utilities to compute code size
|
||||
-- in terms of textual length and AST.
|
||||
-- |
|
||||
-- SPDX-License-Identifier: BSD-3-Clause
|
||||
--
|
||||
-- Types and utilities to compute code size
|
||||
-- in terms of textual length and AST nodes.
|
||||
module Swarm.Game.Scenario.Scoring.CodeSize where
|
||||
|
||||
import Control.Monad (guard)
|
||||
|
@ -1,6 +1,9 @@
|
||||
{-# LANGUAGE TemplateHaskell #-}
|
||||
|
||||
-- | Data types and instances for specific scoring methods
|
||||
-- |
|
||||
-- SPDX-License-Identifier: BSD-3-Clause
|
||||
--
|
||||
-- Data types and instances for specific scoring methods
|
||||
module Swarm.Game.Scenario.Scoring.ConcreteMetrics where
|
||||
|
||||
import Control.Lens hiding (from, (<.>))
|
||||
|
@ -1,4 +1,7 @@
|
||||
-- | Data types and functions applicable across different
|
||||
-- |
|
||||
-- SPDX-License-Identifier: BSD-3-Clause
|
||||
--
|
||||
-- Data types and functions applicable across different
|
||||
-- scoring methods.
|
||||
module Swarm.Game.Scenario.Scoring.GenericMetrics where
|
||||
|
||||
@ -36,10 +39,10 @@ getMetric (Metric _ x) = x
|
||||
-- for incomplete games (rationale: more play = more fun),
|
||||
-- whereas "smaller inputs are better" for completed games.
|
||||
--
|
||||
-- Since "Maybe" has its own "Ord" instance where
|
||||
-- Since 'Maybe' has its own 'Ord' instance where
|
||||
-- @Nothing < Just x@ regardless of @x@, when we want to
|
||||
-- choose the minimum value we `fmap Down` to ensure that
|
||||
-- the `Just` is selected while inverting the ordering of
|
||||
-- choose the minimum value we @fmap Down@ to ensure that
|
||||
-- the 'Just' is selected while inverting the ordering of
|
||||
-- the inner member.
|
||||
chooseBetter ::
|
||||
Ord a =>
|
||||
|
@ -2,7 +2,10 @@
|
||||
{-# LANGUAGE TemplateHaskell #-}
|
||||
{-# OPTIONS_GHC -Wno-orphans #-}
|
||||
|
||||
-- | High-level status of scenario play.
|
||||
-- |
|
||||
-- SPDX-License-Identifier: BSD-3-Clause
|
||||
--
|
||||
-- High-level status of scenario play.
|
||||
-- Representation of progress, logic for updating.
|
||||
module Swarm.Game.Scenario.Status where
|
||||
|
||||
@ -26,8 +29,9 @@ import Swarm.Game.World.Gen (Seed)
|
||||
import Swarm.Util.Lens (makeLensesNoSigs)
|
||||
|
||||
-- | These launch parameters are used in a number of ways:
|
||||
--
|
||||
-- * Serializing the seed/script path for saves
|
||||
-- * Holding parse status from form fields, including Error info
|
||||
-- * Holding parse status from form fields, including error info
|
||||
-- * Carrying fully-validated launch parameters.
|
||||
--
|
||||
-- Type parameters are utilized to support all of these use cases.
|
||||
@ -45,9 +49,9 @@ deriving instance Generic SerializableLaunchParams
|
||||
deriving instance FromJSON SerializableLaunchParams
|
||||
deriving instance ToJSON SerializableLaunchParams
|
||||
|
||||
-- | A "ScenarioStatus" stores the status of a scenario along with
|
||||
-- appropriate metadata: "NotStarted", or "Played".
|
||||
-- The "Played" status has two sub-states: "Attempted" or "Completed".
|
||||
-- | A 'ScenarioStatus' stores the status of a scenario along with
|
||||
-- appropriate metadata: 'NotStarted', or 'Played'.
|
||||
-- The 'Played' status has two sub-states: 'Attempted' or 'Completed'.
|
||||
data ScenarioStatus
|
||||
= NotStarted
|
||||
| Played
|
||||
@ -68,9 +72,9 @@ getLaunchParams = \case
|
||||
NotStarted -> LaunchParams (pure Nothing) (pure Nothing)
|
||||
Played x _ _ -> x
|
||||
|
||||
-- | A "ScenarioInfo" record stores metadata about a scenario: its
|
||||
-- | A 'ScenarioInfo' record stores metadata about a scenario: its
|
||||
-- canonical path and status.
|
||||
-- By way of the "ScenarioStatus" record, it stores the
|
||||
-- By way of the 'ScenarioStatus' record, it stores the
|
||||
-- most recent status and best-ever status.
|
||||
data ScenarioInfo = ScenarioInfo
|
||||
{ _scenarioPath :: FilePath
|
||||
@ -95,11 +99,11 @@ scenarioPath :: Lens' ScenarioInfo FilePath
|
||||
-- | The status of the scenario.
|
||||
scenarioStatus :: Lens' ScenarioInfo ScenarioStatus
|
||||
|
||||
-- | Update the current "ScenarioInfo" record when quitting a game.
|
||||
-- | Update the current 'ScenarioInfo' record when quitting a game.
|
||||
--
|
||||
-- Note that when comparing \"best\" times, shorter is not always better!
|
||||
-- As long as the scenario is not completed (e.g. some do not have win condition)
|
||||
-- we consider having fun _longer_ to be better.
|
||||
-- we consider having fun /longer/ to be better.
|
||||
updateScenarioInfoOnFinish ::
|
||||
CodeSizeDeterminators ->
|
||||
ZonedTime ->
|
||||
|
@ -1,5 +1,7 @@
|
||||
-- |
|
||||
-- SPDX-License-Identifier: BSD-3-Clause
|
||||
--
|
||||
-- Types for styling custom entity attributes
|
||||
module Swarm.Game.Scenario.Style where
|
||||
|
||||
import Data.Aeson
|
||||
|
@ -1,5 +1,7 @@
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
|
||||
-- |
|
||||
-- SPDX-License-Identifier: BSD-3-Clause
|
||||
module Swarm.Game.Scenario.Topography.Area where
|
||||
|
||||
import Data.Int (Int32)
|
||||
@ -22,7 +24,7 @@ invertY (V2 x y) = V2 x (-y)
|
||||
|
||||
-- | Incorporates an offset by -1, since the area is
|
||||
-- "inclusive" of the lower-right coordinate.
|
||||
-- Inverse of "cornersToArea".
|
||||
-- Inverse of 'cornersToArea'.
|
||||
upperLeftToBottomRight :: AreaDimensions -> Location -> Location
|
||||
upperLeftToBottomRight (AreaDimensions w h) upperLeft =
|
||||
upperLeft .+^ displacement
|
||||
@ -30,9 +32,9 @@ upperLeftToBottomRight (AreaDimensions w h) upperLeft =
|
||||
displacement = invertY $ subtract 1 <$> V2 w h
|
||||
|
||||
-- | Converts the displacement vector between the two
|
||||
-- diagonal corners of the rectangle into an "AreaDimensions" record.
|
||||
-- diagonal corners of the rectangle into an 'AreaDimensions' record.
|
||||
-- Adds one to both dimensions since the corner coordinates are "inclusive".
|
||||
-- Inverse of "upperLeftToBottomRight".
|
||||
-- Inverse of 'upperLeftToBottomRight'.
|
||||
cornersToArea :: Location -> Location -> AreaDimensions
|
||||
cornersToArea upperLeft lowerRight =
|
||||
AreaDimensions x y
|
||||
|
@ -31,8 +31,8 @@ import Swarm.Util.Yaml
|
||||
|
||||
-- | A single cell in a world map, which contains a terrain value,
|
||||
-- and optionally an entity and robot.
|
||||
-- It is parameterized on the Entity type to facilitate less
|
||||
-- stateful versions of the Entity type in rendering scenario data.
|
||||
-- It is parameterized on the 'Entity' type to facilitate less
|
||||
-- stateful versions of the 'Entity' type in rendering scenario data.
|
||||
data PCell e = Cell
|
||||
{ cellTerrain :: TerrainType
|
||||
, cellEntity :: Erasable e
|
||||
@ -51,7 +51,7 @@ data AugmentedCell e = AugmentedCell
|
||||
}
|
||||
deriving (Eq, Show)
|
||||
|
||||
-- | Re-usable serialization for variants of "PCell"
|
||||
-- | Re-usable serialization for variants of 'PCell'
|
||||
mkPCellJson :: ToJSON b => (Erasable a -> Maybe b) -> PCell a -> Value
|
||||
mkPCellJson modifier x =
|
||||
toJSON $
|
||||
@ -115,7 +115,7 @@ instance FromJSONE (EntityMap, RobotMap) (AugmentedCell Entity) where
|
||||
-- for rendering.
|
||||
type CellPaintDisplay = PCell EntityFacade
|
||||
|
||||
-- Note: This instance is used only for the purpose of WorldPalette
|
||||
-- Note: This instance is used only for the purpose of 'WorldPalette'
|
||||
instance ToJSON CellPaintDisplay where
|
||||
toJSON = mkPCellJson $ \case
|
||||
ENothing -> Nothing
|
||||
|
@ -1,6 +1,9 @@
|
||||
{-# LANGUAGE DerivingVia #-}
|
||||
|
||||
-- | Stand-in type for an "Entity" for purposes
|
||||
-- |
|
||||
-- SPDX-License-Identifier: BSD-3-Clause
|
||||
--
|
||||
-- Stand-in type for an "Entity" for purposes
|
||||
-- that do not require carrying around the entire state
|
||||
-- of an Entity.
|
||||
--
|
||||
|
@ -3,6 +3,15 @@
|
||||
|
||||
-- |
|
||||
-- SPDX-License-Identifier: BSD-3-Clause
|
||||
--
|
||||
-- Type definitions and validation logic for portals.
|
||||
--
|
||||
-- Portals can be inter-world or intra-world.
|
||||
-- It is legal for a portal exit to be on the same cell as its entrance.
|
||||
--
|
||||
-- By default, passage through a portal preserves the orientation
|
||||
-- of the robot, but an extra portal parameter can specify
|
||||
-- that the robot should be re-oriented.
|
||||
module Swarm.Game.Scenario.Topography.Navigation.Portal where
|
||||
|
||||
import Control.Arrow ((&&&))
|
||||
@ -40,12 +49,14 @@ data AnnotatedDestination a = AnnotatedDestination
|
||||
|
||||
-- | Parameterized on waypoint dimensionality ('additionalDimension') and
|
||||
-- on the portal location specification method ('portalExitLoc').
|
||||
--
|
||||
-- == @additionalDimension@
|
||||
-- As a member of the 'WorldDescription', waypoints are only known within a
|
||||
-- a single subworld, so 'additionalDimension' is 'Identity' for the map
|
||||
-- of waypoint names to planar locations.
|
||||
-- At the Scenario level, in contrast, we have access to all subworlds, so
|
||||
-- we nest this map to planar locations in additional mapping layer by subworld.
|
||||
--
|
||||
-- == @portalExitLoc@
|
||||
-- At the subworld parsing level, we only can obtain the planar location
|
||||
-- for portal /entrances/, but the /exits/ remain as waypoint names.
|
||||
@ -110,11 +121,12 @@ failWaypointLookup (WaypointName rawName) =
|
||||
|
||||
-- |
|
||||
-- The following constraints must be enforced:
|
||||
--
|
||||
-- * portals based on plural waypoint multiplicity can have multiple entrances but only a single exit
|
||||
-- * no two portals share the same entrance location
|
||||
-- * waypoint uniqueness within a subworld when the 'unique' flag is specified
|
||||
--
|
||||
-- == Data flow:
|
||||
-- == Data flow
|
||||
--
|
||||
-- Waypoints are defined within a subworld and are namespaced by it.
|
||||
-- Optional intra-subworld uniqueness of Waypoints is enforced at WorldDescription
|
||||
@ -217,6 +229,7 @@ validatePortals (Navigation wpUniverse partialPortals) = do
|
||||
--
|
||||
-- Verifying this is simple:
|
||||
-- For all of the portals between Subworlds A and B:
|
||||
--
|
||||
-- * The coordinates of all \"consistent\" portal locations in Subworld A
|
||||
-- are subtracted from the corresponding coordinates in Subworld B. It
|
||||
-- does not matter which are exits vs. entrances.
|
||||
@ -271,6 +284,7 @@ ensureSpatialConsistency xs =
|
||||
--
|
||||
-- == Discussion
|
||||
-- Compare to the 'Traversable' instance of 'Signed':
|
||||
--
|
||||
-- @
|
||||
-- instance Traversable Signed where
|
||||
-- traverse f (Positive x) = Positive <$> f x
|
||||
@ -278,6 +292,7 @@ ensureSpatialConsistency xs =
|
||||
-- @
|
||||
--
|
||||
-- if we were to substitute 'id' for f:
|
||||
--
|
||||
-- @
|
||||
-- traverse id (Positive x) = Positive <$> id x
|
||||
-- traverse id (Negative x) = Negative <$> id x
|
||||
|
@ -2,6 +2,9 @@
|
||||
|
||||
-- |
|
||||
-- SPDX-License-Identifier: BSD-3-Clause
|
||||
--
|
||||
-- Descriptions of the orientation and offset by
|
||||
-- which a structure should be placed.
|
||||
module Swarm.Game.Scenario.Topography.Placement where
|
||||
|
||||
import Data.List (transpose)
|
||||
|
@ -2,6 +2,9 @@
|
||||
|
||||
-- |
|
||||
-- SPDX-License-Identifier: BSD-3-Clause
|
||||
--
|
||||
-- Definitions of "structures" for use within a map,
|
||||
-- as well as logic for combining them.
|
||||
module Swarm.Game.Scenario.Topography.Structure where
|
||||
|
||||
import Control.Applicative ((<|>))
|
||||
@ -94,7 +97,7 @@ overlaySingleStructure
|
||||
else drop $ abs integralOffset
|
||||
|
||||
-- | Overlays all of the "child placements", such that the children encountered earlier
|
||||
-- in the YAML file supersede the later ones (due to use of "foldr" instead of "foldl").
|
||||
-- in the YAML file supersede the later ones (due to use of 'foldr' instead of 'foldl').
|
||||
mergeStructures ::
|
||||
M.Map StructureName (PStructure (Maybe a)) ->
|
||||
Maybe Placement ->
|
||||
@ -121,7 +124,7 @@ instance FromJSONE (EntityMap, RobotMap) (PStructure (Maybe (PCell Entity))) whe
|
||||
(maskedArea, mapWaypoints) <- liftE $ (v .:? "map" .!= "") >>= paintMap maybeMaskChar pal
|
||||
return $ Structure maskedArea localStructureDefs placementDefs $ waypointDefs <> mapWaypoints
|
||||
|
||||
-- | "Paint" a world map using a 'WorldPalette', turning it from a raw
|
||||
-- | \"Paint\" a world map using a 'WorldPalette', turning it from a raw
|
||||
-- string into a nested list of 'Cell' values by looking up each
|
||||
-- character in the palette, failing if any character in the raw map
|
||||
-- is not contained in the palette.
|
||||
|
@ -27,7 +27,7 @@ renderWorldName = \case
|
||||
|
||||
-- | The swarm universe consists of locations
|
||||
-- indexed by subworld.
|
||||
-- Not only is this datatype useful for planar (2D)
|
||||
-- Not only is this parameterized datatype useful for planar (2D)
|
||||
-- coordinates, but is also used for named waypoints.
|
||||
data Cosmic a = Cosmic
|
||||
{ _subworld :: SubworldName
|
||||
|
@ -2,10 +2,10 @@
|
||||
{-# OPTIONS_GHC -fno-warn-orphans #-}
|
||||
|
||||
-- |
|
||||
-- SPDX-License-Identifier: BSD-3-Clause
|
||||
--
|
||||
-- Conversions from native Haskell values
|
||||
-- to values in the swarm language.
|
||||
--
|
||||
-- SPDX-License-Identifier: BSD-3-Clause
|
||||
module Swarm.Game.Value where
|
||||
|
||||
import Control.Lens (view)
|
||||
|
@ -35,11 +35,11 @@ newtype Coords = Coords {unCoords :: (Int32, Int32)}
|
||||
instance Rewrapped Coords t
|
||||
instance Wrapped Coords
|
||||
|
||||
-- | Convert an external (x,y) location to an internal 'Coords' value.
|
||||
-- | Convert an external @(x,y)@ location to an internal 'Coords' value.
|
||||
locToCoords :: Location -> Coords
|
||||
locToCoords (Location x y) = Coords (-y, x)
|
||||
|
||||
-- | Convert an internal 'Coords' value to an external (x,y) location.
|
||||
-- | Convert an internal 'Coords' value to an external @(x,y)@ location.
|
||||
coordsToLoc :: Coords -> Location
|
||||
coordsToLoc (Coords (r, c)) = Location c (-r)
|
||||
|
||||
|
@ -44,7 +44,7 @@ import Witch.From (from)
|
||||
-- See https://en.wikipedia.org/wiki/Polar_coordinate_system#Conventions
|
||||
--
|
||||
-- Do not alter this ordering, as there exist functions that depend on it
|
||||
-- (e.g. "nearestDirection" and "relativeTo").
|
||||
-- (e.g. 'nearestDirection' and 'relativeTo').
|
||||
data AbsoluteDir = DEast | DNorth | DWest | DSouth
|
||||
deriving (Eq, Ord, Show, Read, Generic, Data, Hashable, Enum, Bounded)
|
||||
|
||||
@ -82,7 +82,7 @@ data RelativeDir = DPlanar PlanarRelativeDir | DDown
|
||||
deriving (Eq, Ord, Show, Read, Generic, Data, Hashable, ToJSON, FromJSON)
|
||||
|
||||
-- | Caution: Do not alter this ordering, as there exist functions that depend on it
|
||||
-- (e.g. "nearestDirection" and "relativeTo").
|
||||
-- (e.g. 'nearestDirection' and 'relativeTo').
|
||||
data PlanarRelativeDir = DForward | DLeft | DBack | DRight
|
||||
deriving (Eq, Ord, Show, Read, Generic, Data, Hashable, Enum, Bounded)
|
||||
|
||||
@ -98,7 +98,7 @@ data Direction = DAbsolute AbsoluteDir | DRelative RelativeDir
|
||||
deriving (Eq, Ord, Show, Read, Generic, Data, Hashable, ToJSON, FromJSON)
|
||||
|
||||
-- | Direction name is generated from the deepest nested data constructor
|
||||
-- e.g. DLeft becomes "left"
|
||||
-- e.g. 'DLeft' becomes "left"
|
||||
directionSyntax :: Direction -> Text
|
||||
directionSyntax d = toLower . T.tail . from $ case d of
|
||||
DAbsolute x -> show x
|
||||
|
@ -1,5 +1,7 @@
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
|
||||
-- |
|
||||
-- SPDX-License-Identifier: BSD-3-Clause
|
||||
module Swarm.Language.LSP.Hover (
|
||||
showHoverInfo,
|
||||
|
||||
|
@ -1,7 +1,7 @@
|
||||
-- |
|
||||
-- SPDX-License-Identifier: BSD-3-Clause
|
||||
--
|
||||
-- Ensures that access to an IORef is read-only
|
||||
-- Ensures that access to an 'IORef' is read-only
|
||||
-- by hiding behind a newtype.
|
||||
module Swarm.ReadableIORef (mkReadonly, ReadableIORef, readIORef) where
|
||||
|
||||
|
@ -1,5 +1,7 @@
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
|
||||
-- |
|
||||
-- SPDX-License-Identifier: BSD-3-Clause
|
||||
module Swarm.TUI.Editor.Controller where
|
||||
|
||||
import Brick hiding (Direction (..), Location (..))
|
||||
|
@ -1,3 +1,5 @@
|
||||
-- |
|
||||
-- SPDX-License-Identifier: BSD-3-Clause
|
||||
module Swarm.TUI.Editor.Json where
|
||||
|
||||
import Data.Text (Text)
|
||||
|
@ -1,3 +1,5 @@
|
||||
-- |
|
||||
-- SPDX-License-Identifier: BSD-3-Clause
|
||||
module Swarm.TUI.Editor.Masking where
|
||||
|
||||
import Control.Lens hiding (Const, from)
|
||||
|
@ -1,6 +1,8 @@
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{-# LANGUAGE TemplateHaskell #-}
|
||||
|
||||
-- |
|
||||
-- SPDX-License-Identifier: BSD-3-Clause
|
||||
module Swarm.TUI.Editor.Model where
|
||||
|
||||
import Brick.Focus
|
||||
|
@ -1,3 +1,5 @@
|
||||
-- |
|
||||
-- SPDX-License-Identifier: BSD-3-Clause
|
||||
module Swarm.TUI.Editor.Util where
|
||||
|
||||
import Control.Applicative ((<|>))
|
||||
|
@ -1,3 +1,5 @@
|
||||
-- |
|
||||
-- SPDX-License-Identifier: BSD-3-Clause
|
||||
module Swarm.TUI.Editor.View where
|
||||
|
||||
import Brick hiding (Direction)
|
||||
|
@ -44,7 +44,7 @@ cacheValidatedInputs = do
|
||||
editingParams .= parsedParams
|
||||
updateFocusRing parsedParams
|
||||
|
||||
-- | Split this out from the combined parameter-validation function
|
||||
-- | This is split out from the combined parameter-validation function
|
||||
-- because validating the seed is cheap, and shouldn't have to pay
|
||||
-- the cost of re-parsing script code as the user types in the seed
|
||||
-- selection field.
|
||||
@ -57,7 +57,7 @@ cacheValidatedSeedInput = do
|
||||
editingParams .= newParams
|
||||
updateFocusRing newParams
|
||||
|
||||
-- | If the FileBrowser is in "search mode", then we allow
|
||||
-- | If the 'FileBrowser' is in "search mode", then we allow
|
||||
-- more of the key events to pass through. Otherwise,
|
||||
-- we intercept things like "q" (for quit) and Space (so that
|
||||
-- we can restrict file selection to at most one).
|
||||
|
@ -70,10 +70,10 @@ initEditorWidget =
|
||||
(Just 1) -- only allow a single line
|
||||
|
||||
-- | Called before any particular scenario is selected, so we
|
||||
-- supply some "Nothing"s as defaults to the "ValidatedLaunchParams".
|
||||
-- supply some 'Nothing's as defaults to the 'ValidatedLaunchParams'.
|
||||
initConfigPanel :: IO LaunchOptions
|
||||
initConfigPanel = do
|
||||
-- NOTE: This is kind of pointless, because we must re-instantiate the FileBrowser
|
||||
-- NOTE: This is kind of pointless, because we must re-instantiate the 'FileBrowser'
|
||||
-- when it is first displayed, anyway.
|
||||
fb <-
|
||||
FB.newFileBrowser
|
||||
@ -108,10 +108,11 @@ initFileBrowserWidget maybePlayedScript = do
|
||||
-- Note that the FileBrowser widget normally allows multiple selections ("marked" files).
|
||||
-- However, there do not exist any public "setters" set the marked files, so we have
|
||||
-- some workarounds:
|
||||
-- * When the user marks the first file, we immediately close the FileBrowser widget.
|
||||
-- * We re-instantiate the FileBrowser from scratch every time it is opened, so that
|
||||
--
|
||||
-- * When the user marks the first file, we immediately close the 'FileBrowser' widget.
|
||||
-- * We re-instantiate the 'FileBrowser' from scratch every time it is opened, so that
|
||||
-- it is not possible to mark more than one file.
|
||||
-- * The "marked file" is persisted outside of the FileBrowser state, and the
|
||||
-- * The "marked file" is persisted outside of the 'FileBrowser' state, and the
|
||||
-- "initial directory" is set upon instantiation from that external state.
|
||||
prepareLaunchDialog ::
|
||||
ScenarioInfoPair ->
|
||||
|
@ -6,6 +6,9 @@
|
||||
|
||||
-- |
|
||||
-- SPDX-License-Identifier: BSD-3-Clause
|
||||
--
|
||||
-- Sum types that represent menu options,
|
||||
-- modal dialogs, and buttons.
|
||||
module Swarm.TUI.Model.Menu where
|
||||
|
||||
import Brick.Widgets.Dialog (Dialog)
|
||||
|
@ -1,5 +1,11 @@
|
||||
-- |
|
||||
-- SPDX-License-Identifier: BSD-3-Clause
|
||||
--
|
||||
-- Sum types representing the Brick names
|
||||
-- for every referenceable widget.
|
||||
--
|
||||
-- Nesting of name types is utilized often to simplify
|
||||
-- case matching.
|
||||
module Swarm.TUI.Model.Name where
|
||||
|
||||
data WorldEditorFocusable
|
||||
|
Loading…
Reference in New Issue
Block a user