Skip to content

Commit

Permalink
disambiguate doc links, elaborate waypoint ordering
Browse files Browse the repository at this point in the history
  • Loading branch information
kostmo committed Sep 17, 2023
1 parent b329a43 commit bb0e72b
Show file tree
Hide file tree
Showing 6 changed files with 53 additions and 20 deletions.
2 changes: 2 additions & 0 deletions src/Swarm/Game/Scenario/Style.hs
Original file line number Diff line number Diff line change
Expand Up @@ -32,6 +32,8 @@ instance FromJSON StyleFlag where
instance ToJSON StyleFlag where
toJSON = genericToJSON styleFlagJsonOptions

-- | Hexadecimal color notation.
-- May include a leading hash symbol (see 'Data.Colour.SRGB.sRGB24read').
newtype HexColor = HexColor Text
deriving (Eq, Show, Generic, FromJSON, ToJSON)

Expand Down
16 changes: 16 additions & 0 deletions src/Swarm/Game/Scenario/Topography/Navigation/Waypoint.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,6 +2,22 @@

-- |
-- SPDX-License-Identifier: BSD-3-Clause
--
-- Landmarks that are used to specify portal locations
-- and can serve as navigation aids via the `waypoint` command.
--
-- = Waypoint ordering
--
-- The sequence of waypoints of a given name is dictated by criteria in the following order:
--
-- 1. Ordering of structure placements
-- (see implementation of 'Swarm.Game.Scenario.Topography.Structure.mergeStructures');
-- later placements are ordered first.
-- 2. Placement of cells within a map. Map locations go by row-major order
-- (compare to docs for 'Swarm.Game.State.genRobotTemplates').
--
-- TODO (#1366): May be useful to have a mechanism for more
-- precise control of ordering.
module Swarm.Game.Scenario.Topography.Navigation.Waypoint where

import Data.Int (Int32)
Expand Down
15 changes: 13 additions & 2 deletions src/Swarm/Game/Universe.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,6 +3,9 @@

-- |
-- SPDX-License-Identifier: BSD-3-Clause
--
-- Types and utilities for working with "universal locations";
-- locations that encompass different 2-D subworlds.
module Swarm.Game.Universe where

import Control.Lens (makeLenses, view)
Expand All @@ -14,6 +17,8 @@ import GHC.Generics (Generic)
import Linear (V2 (..))
import Swarm.Game.Location

-- * Referring to subworlds

data SubworldName = DefaultRootSubworld | SubworldName Text
deriving (Show, Eq, Ord, Generic, ToJSON)

Expand All @@ -25,6 +30,8 @@ renderWorldName = \case
SubworldName s -> s
DefaultRootSubworld -> "<default>"

-- * Universal location

-- | The swarm universe consists of locations
-- indexed by subworld.
-- Not only is this parameterized datatype useful for planar (2D)
Expand All @@ -47,8 +54,7 @@ instance (FromJSON a) => FromJSON (Cosmic a) where
<$> v .: "subworld"
<*> v .: "loc"

defaultCosmicLocation :: Cosmic Location
defaultCosmicLocation = Cosmic DefaultRootSubworld origin
-- * Measurement

data DistanceMeasure b = Measurable b | InfinitelyFar
deriving (Eq, Ord)
Expand All @@ -59,5 +65,10 @@ cosmoMeasure f a b
| ((/=) `on` view subworld) a b = InfinitelyFar
| otherwise = Measurable $ (f `on` view planar) a b

-- * Utilities

defaultCosmicLocation :: Cosmic Location
defaultCosmicLocation = Cosmic DefaultRootSubworld origin

offsetBy :: Cosmic Location -> V2 Int32 -> Cosmic Location
offsetBy loc v = fmap (.+^ v) loc
4 changes: 2 additions & 2 deletions src/Swarm/TUI/Controller.hs
Original file line number Diff line number Diff line change
Expand Up @@ -10,7 +10,7 @@ module Swarm.TUI.Controller (
handleEvent,
quitGame,

-- ** Handling 'Frame' events
-- ** Handling 'Swarm.TUI.Model.Frame' events
runFrameUI,
runFrame,
ticksPerFrameCap,
Expand Down Expand Up @@ -646,7 +646,7 @@ runFrameUI = do
-- | Run the game for a single frame, without updating the UI.
runFrame :: EventM Name AppState ()
runFrame = do
-- Reset the needsRedraw flag. While procssing the frame and stepping the robots,
-- Reset the needsRedraw flag. While processing the frame and stepping the robots,
-- the flag will get set to true if anything changes that requires redrawing the
-- world (e.g. a robot moving or disappearing).
gameState . needsRedraw .= False
Expand Down
29 changes: 16 additions & 13 deletions src/Swarm/TUI/Model/UI.hs
Original file line number Diff line number Diff line change
Expand Up @@ -136,8 +136,11 @@ makeLensesExcluding ['_lgTicksPerSecond] ''UIState
-- | The current menu state.
uiMenu :: Lens' UIState Menu

-- | Are we currently playing the game? True = we are playing, and
-- should thus display a world, REPL, etc.; False = we should
-- | Are we currently playing the game?
--
-- * 'True' = we are playing, and
-- should thus display a world, REPL, etc.
-- * False = we should
-- display the current menu.
uiPlaying :: Lens' UIState Bool

Expand All @@ -148,7 +151,7 @@ uiCheatMode :: Lens' UIState Bool
uiLaunchConfig :: Lens' UIState LaunchOptions

-- | The focus ring is the set of UI panels we can cycle among using
-- the Tab key.
-- the @Tab@ key.
uiFocusRing :: Lens' UIState (FocusRing Name)

-- | The last clicked position on the world view.
Expand All @@ -175,29 +178,29 @@ uiInventory :: Lens' UIState (Maybe (Int, BL.List Name InventoryListEntry))
-- (used when a new log message is appended).
uiScrollToEnd :: Lens' UIState Bool

-- | When this is @Just@, it represents a modal to be displayed on
-- | When this is 'Just', it represents a modal to be displayed on
-- top of the UI, e.g. for the Help screen.
uiModal :: Lens' UIState (Maybe Modal)

-- | Status of the scenario goal: whether there is one, and whether it
-- has been displayed to the user initially.
uiGoal :: Lens' UIState GoalDisplay

-- | When running with --autoplay, suppress the goal dialogs.
-- | When running with @--autoplay@, suppress the goal dialogs.
--
-- For developement, the --cheat flag shows goals again.
-- For development, the @--cheat@ flag shows goals again.
uiHideGoals :: Lens' UIState Bool

-- | Map of achievements that were attained
uiAchievements :: Lens' UIState (Map CategorizedAchievement Attainment)

-- | A toggle to show the FPS by pressing `f`
-- | A toggle to show the FPS by pressing @f@
uiShowFPS :: Lens' UIState Bool

-- | A toggle to expand or collapse the REPL by pressing `Ctrl-k`
-- | A toggle to expand or collapse the REPL by pressing @Ctrl-k@
uiShowREPL :: Lens' UIState Bool

-- | A toggle to show or hide inventory items with count 0 by pressing `0`
-- | A toggle to show or hide inventory items with count 0 by pressing @0@
uiShowZero :: Lens' UIState Bool

-- | A toggle to show debug.
Expand All @@ -215,10 +218,10 @@ uiShowRobots = to (\ui -> ui ^. lastFrameTime > ui ^. uiHideRobotsUntil)
-- | Whether the Inventory ui panel should update
uiInventoryShouldUpdate :: Lens' UIState Bool

-- | Computed ticks per milli seconds
-- | Computed ticks per milliseconds
uiTPF :: Lens' UIState Double

-- | Computed frames per milli seconds
-- | Computed frames per milliseconds
uiFPS :: Lens' UIState Double

-- | Attribute map
Expand Down Expand Up @@ -256,10 +259,10 @@ frameTickCount :: Lens' UIState Int
-- | The time of the last info widget update
lastInfoTime :: Lens' UIState TimeSpec

-- | The time of the last 'Frame' event.
-- | The time of the last 'Swarm.TUI.Model.Frame' event.
lastFrameTime :: Lens' UIState TimeSpec

-- | The amount of accumulated real time. Every time we get a 'Frame'
-- | The amount of accumulated real time. Every time we get a 'Swarm.TUI.Model.Frame'
-- event, we accumulate the amount of real time that happened since
-- the last frame, then attempt to take an appropriate number of
-- ticks to "catch up", based on the target tick rate.
Expand Down
7 changes: 4 additions & 3 deletions src/Swarm/TUI/View.hs
Original file line number Diff line number Diff line change
Expand Up @@ -24,6 +24,7 @@ module Swarm.TUI.View (
drawRobotPanel,
drawItem,
drawLabelledEntityName,
renderDutyCycle,

-- * Info panel
drawInfoPanel,
Expand Down Expand Up @@ -645,10 +646,10 @@ drawModal s = \case
-- due to the sliding window.
--
-- == Use of previous tick
-- The 'gameTick' function runs all robots, then increments the current tick.
-- The 'Swarm.Game.Step.gameTick' function runs all robots, then increments the current tick.
-- So at the time we are rendering a frame, the current tick will always be
-- strictly greater than any ticks stored in the 'WindowedCounter' for any robot;
-- hence 'getOccupancy' will never be @1@ if we use the current tick directly as
-- strictly greater than any ticks stored in the 'WC.WindowedCounter' for any robot;
-- hence 'WC.getOccupancy' will never be @1@ if we use the current tick directly as
-- obtained from the 'ticks' function.
-- So we "rewind" it to the previous tick for the purpose of this display.
renderDutyCycle :: GameState -> Robot -> Widget Name
Expand Down

0 comments on commit bb0e72b

Please sign in to comment.