Skip to content

Commit

Permalink
better encapsulate state
Browse files Browse the repository at this point in the history
  • Loading branch information
kostmo committed Sep 7, 2024
1 parent 72d31e8 commit 6fcb748
Showing 1 changed file with 32 additions and 12 deletions.
44 changes: 32 additions & 12 deletions src/swarm-tui/Swarm/TUI/View/Robot.hs
Original file line number Diff line number Diff line change
@@ -1,12 +1,15 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE NoGeneralizedNewtypeDeriving #-}
{-# LANGUAGE TemplateHaskell #-}

-- |
-- SPDX-License-Identifier: BSD-3-Clause
--
-- A UI-centric model for presentation of Robot details.
module Swarm.TUI.View.Robot where

import Data.Set (Set)
import Control.Lens hiding (from, (<.>))
import Brick hiding (Direction, Location)
import Brick.Widgets.Center (hCenter)
import Brick.Widgets.Table qualified as BT
Expand Down Expand Up @@ -39,6 +42,15 @@ import Swarm.Util.UnitInterval
import Swarm.Util.WindowedCounter qualified as WC
import System.Clock (TimeSpec (..))

data RobotRenderingContext = RobotRenderingContext {
_mygs :: GameState
, _gameplay :: UIGameplay
, _timing :: UITiming
, _uiDbg :: Set DebugOption
}

makeLenses ''RobotRenderingContext

-- | Render the percentage of ticks that this robot was active.
-- This indicator can take some time to "warm up" and stabilize
-- due to the sliding window.
Expand All @@ -50,11 +62,11 @@ import System.Clock (TimeSpec (..))
-- 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
renderDutyCycle gs robot =
renderDutyCycle :: TemporalState -> Robot -> Widget Name
renderDutyCycle temporalState robot =
withAttr dutyCycleAttr . str . flip (showFFloat (Just 1)) "%" $ dutyCyclePercentage
where
curTicks = gs ^. temporal . ticks
curTicks = temporalState ^. ticks
window = robot ^. activityCounts . activityWindow

-- Rewind to previous tick
Expand All @@ -75,10 +87,18 @@ robotsListWidget s = hCenter table
. BT.setDefaultColAlignment BT.AlignCenter
-- Inventory count is right aligned
. BT.alignRight 4
$ robotsTable s
$ robotsTable c

c = RobotRenderingContext {
_mygs = s ^. gameState
, _gameplay = s ^. uiState . uiGameplay
, _timing = s ^. uiState . uiGameplay . uiTiming
, _uiDbg = s ^. uiState . uiDebugOptions
}


robotsTable :: AppState -> BT.Table Name
robotsTable s =
robotsTable :: RobotRenderingContext -> BT.Table Name
robotsTable c =
BT.table $
map (padLeftRight 1) <$> (headers : robotRows)
where
Expand Down Expand Up @@ -110,7 +130,7 @@ robotsTable s =
-- a per-robot pop-up
str . show . sum . M.elems $ robot ^. activityCounts . commandsHistogram
, str $ show $ robot ^. activityCounts . lifetimeStepCount
, renderDutyCycle (s ^. gameState) robot
, renderDutyCycle (c ^. mygs . temporal) robot
, txt rLog
]

Expand All @@ -130,7 +150,7 @@ robotsTable s =
| otherwise = show (age `div` 3600 * 24) <> "day"
where
TimeSpec createdAtSec _ = robot ^. robotCreatedAt
TimeSpec nowSec _ = s ^. uiState . uiGameplay . uiTiming . lastFrameTime
TimeSpec nowSec _ = c ^. timing . lastFrameTime
age = nowSec - createdAtSec

rInvCount = sum $ map fst . E.elems $ robot ^. robotEntity . entityInventory
Expand All @@ -144,7 +164,7 @@ robotsTable s =
rLoc = robot ^. robotLocation
worldCell =
drawLoc
(s ^. uiState . uiGameplay)
(c ^. gameplay)
g
rCoords
locStr = renderCoordsString rLoc
Expand All @@ -167,6 +187,6 @@ robotsTable s =
. IM.elems
$ g ^. robotInfo . robotMap
creative = g ^. creativeMode
debugRID = s ^. uiState . uiDebugOptions . Lens.contains ListRobotIDs
debugAllRobots = s ^. uiState . uiDebugOptions . Lens.contains ListAllRobots
g = s ^. gameState
debugRID = c ^. uiDbg . Lens.contains ListRobotIDs
debugAllRobots = c ^. uiDbg . Lens.contains ListAllRobots
g = c ^. mygs

0 comments on commit 6fcb748

Please sign in to comment.