{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE OverloadedRecordDot #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE NoGeneralizedNewtypeDeriving #-}
module Swarm.TUI.View.Robot (
emptyRobotDisplay,
updateRobotList,
robotGridRenderers,
drawRobotsDisplayModal,
getSelectedRobot,
) where
import Brick
import Brick.Focus
import Brick.Widgets.Border
import Brick.Widgets.Center
import Brick.Widgets.List qualified as BL
import Brick.Widgets.TabularList.Grid qualified as BL
import Brick.Widgets.TabularList.Mixed
import Control.Lens as Lens hiding (Const, from)
import Data.IntMap qualified as IM
import Data.List.Extra (dropPrefix, enumerate)
import Data.Map qualified as M
import Data.Maybe (fromMaybe)
import Data.Sequence (Seq)
import Data.Sequence qualified as S
import Data.Set (Set)
import Data.Set qualified as Set
import Data.Text (Text)
import Data.Text qualified as T
import Linear (V2, distance)
import Numeric (showFFloat)
import Swarm.Game.CESK (CESK (..))
import Swarm.Game.Entity as E
import Swarm.Game.Location (Point, origin)
import Swarm.Game.Robot
import Swarm.Game.Robot.Activity
import Swarm.Game.Robot.Concrete
import Swarm.Game.State
import Swarm.Game.State.Robot
import Swarm.Game.State.Substate
import Swarm.Game.Tick (addTicks)
import Swarm.Game.Universe
import Swarm.Game.World.Coords
import Swarm.TUI.Model.DebugOption (DebugOption (..))
import Swarm.TUI.Model.Name
import Swarm.TUI.Model.UI.Gameplay
import Swarm.TUI.View.Attribute.Attr
import Swarm.TUI.View.CellDisplay
import Swarm.TUI.View.Robot.Details
import Swarm.TUI.View.Robot.Type
import Swarm.TUI.View.Shared (tabControlFooter)
import Swarm.Util (applyWhen, maximum0)
import Swarm.Util.UnitInterval
import Swarm.Util.WindowedCounter qualified as WC
import System.Clock (TimeSpec (..))
data RobotColumn
= ColName
| ColAge
| ColPos
| ColItems
| ColStatus
| ColActns
| ColCmds
| ColCycles
| ColActivity
| ColLog
|
ColID
deriving (RobotColumn -> RobotColumn -> Bool
(RobotColumn -> RobotColumn -> Bool)
-> (RobotColumn -> RobotColumn -> Bool) -> Eq RobotColumn
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RobotColumn -> RobotColumn -> Bool
== :: RobotColumn -> RobotColumn -> Bool
$c/= :: RobotColumn -> RobotColumn -> Bool
/= :: RobotColumn -> RobotColumn -> Bool
Eq, Eq RobotColumn
Eq RobotColumn =>
(RobotColumn -> RobotColumn -> Ordering)
-> (RobotColumn -> RobotColumn -> Bool)
-> (RobotColumn -> RobotColumn -> Bool)
-> (RobotColumn -> RobotColumn -> Bool)
-> (RobotColumn -> RobotColumn -> Bool)
-> (RobotColumn -> RobotColumn -> RobotColumn)
-> (RobotColumn -> RobotColumn -> RobotColumn)
-> Ord RobotColumn
RobotColumn -> RobotColumn -> Bool
RobotColumn -> RobotColumn -> Ordering
RobotColumn -> RobotColumn -> RobotColumn
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: RobotColumn -> RobotColumn -> Ordering
compare :: RobotColumn -> RobotColumn -> Ordering
$c< :: RobotColumn -> RobotColumn -> Bool
< :: RobotColumn -> RobotColumn -> Bool
$c<= :: RobotColumn -> RobotColumn -> Bool
<= :: RobotColumn -> RobotColumn -> Bool
$c> :: RobotColumn -> RobotColumn -> Bool
> :: RobotColumn -> RobotColumn -> Bool
$c>= :: RobotColumn -> RobotColumn -> Bool
>= :: RobotColumn -> RobotColumn -> Bool
$cmax :: RobotColumn -> RobotColumn -> RobotColumn
max :: RobotColumn -> RobotColumn -> RobotColumn
$cmin :: RobotColumn -> RobotColumn -> RobotColumn
min :: RobotColumn -> RobotColumn -> RobotColumn
Ord, Int -> RobotColumn
RobotColumn -> Int
RobotColumn -> [RobotColumn]
RobotColumn -> RobotColumn
RobotColumn -> RobotColumn -> [RobotColumn]
RobotColumn -> RobotColumn -> RobotColumn -> [RobotColumn]
(RobotColumn -> RobotColumn)
-> (RobotColumn -> RobotColumn)
-> (Int -> RobotColumn)
-> (RobotColumn -> Int)
-> (RobotColumn -> [RobotColumn])
-> (RobotColumn -> RobotColumn -> [RobotColumn])
-> (RobotColumn -> RobotColumn -> [RobotColumn])
-> (RobotColumn -> RobotColumn -> RobotColumn -> [RobotColumn])
-> Enum RobotColumn
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: RobotColumn -> RobotColumn
succ :: RobotColumn -> RobotColumn
$cpred :: RobotColumn -> RobotColumn
pred :: RobotColumn -> RobotColumn
$ctoEnum :: Int -> RobotColumn
toEnum :: Int -> RobotColumn
$cfromEnum :: RobotColumn -> Int
fromEnum :: RobotColumn -> Int
$cenumFrom :: RobotColumn -> [RobotColumn]
enumFrom :: RobotColumn -> [RobotColumn]
$cenumFromThen :: RobotColumn -> RobotColumn -> [RobotColumn]
enumFromThen :: RobotColumn -> RobotColumn -> [RobotColumn]
$cenumFromTo :: RobotColumn -> RobotColumn -> [RobotColumn]
enumFromTo :: RobotColumn -> RobotColumn -> [RobotColumn]
$cenumFromThenTo :: RobotColumn -> RobotColumn -> RobotColumn -> [RobotColumn]
enumFromThenTo :: RobotColumn -> RobotColumn -> RobotColumn -> [RobotColumn]
Enum, RobotColumn
RobotColumn -> RobotColumn -> Bounded RobotColumn
forall a. a -> a -> Bounded a
$cminBound :: RobotColumn
minBound :: RobotColumn
$cmaxBound :: RobotColumn
maxBound :: RobotColumn
Bounded, Int -> RobotColumn -> ShowS
[RobotColumn] -> ShowS
RobotColumn -> String
(Int -> RobotColumn -> ShowS)
-> (RobotColumn -> String)
-> ([RobotColumn] -> ShowS)
-> Show RobotColumn
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RobotColumn -> ShowS
showsPrec :: Int -> RobotColumn -> ShowS
$cshow :: RobotColumn -> String
show :: RobotColumn -> String
$cshowList :: [RobotColumn] -> ShowS
showList :: [RobotColumn] -> ShowS
Show)
colName :: RobotColumn -> Text
colName :: RobotColumn -> Text
colName = String -> Text
T.pack (String -> Text) -> (RobotColumn -> String) -> RobotColumn -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
forall a. Eq a => [a] -> [a] -> [a]
dropPrefix String
"Col" ShowS -> (RobotColumn -> String) -> RobotColumn -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RobotColumn -> String
forall a. Show a => a -> String
show
colWidth :: RobotColumn -> Int
colWidth :: RobotColumn -> Int
colWidth = Text -> Int
forall a. TextWidth a => a -> Int
textWidth (Text -> Int) -> (RobotColumn -> Text) -> RobotColumn -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RobotColumn -> Text
colName
colWidths :: Set DebugOption -> Seq ColWidth
colWidths :: Set DebugOption -> Seq ColWidth
colWidths Set DebugOption
opt = Int -> ColWidth
ColW (Int -> ColWidth)
-> (RobotColumn -> Int) -> RobotColumn -> ColWidth
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RobotColumn -> Int
getWidth (RobotColumn -> ColWidth) -> Seq RobotColumn -> Seq ColWidth
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [RobotColumn] -> Seq RobotColumn
forall a. [a] -> Seq a
S.fromList [RobotColumn]
robotColumns
where
showIDs :: Bool
showIDs = DebugOption -> Set DebugOption -> Bool
forall a. Ord a => a -> Set a -> Bool
Set.member DebugOption
ListRobotIDs Set DebugOption
opt
robotColumns :: [RobotColumn]
robotColumns :: [RobotColumn]
robotColumns = (if Bool
showIDs then [RobotColumn] -> [RobotColumn]
forall a. a -> a
id else (RobotColumn -> Bool) -> [RobotColumn] -> [RobotColumn]
forall a. (a -> Bool) -> [a] -> [a]
filter (RobotColumn -> RobotColumn -> Bool
forall a. Eq a => a -> a -> Bool
/= RobotColumn
ColID)) [RobotColumn]
forall a. (Enum a, Bounded a) => [a]
enumerate
getWidth :: RobotColumn -> Int
getWidth = \case
RobotColumn
ColName -> Int
26 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ (if Bool
showIDs then Int
0 else RobotColumn -> Int
getWidth RobotColumn
ColID)
RobotColumn
ColAge -> Int
8
RobotColumn
ColPos -> Int
9
RobotColumn
ColStatus -> Int
10
RobotColumn
ColID -> Int
5
RobotColumn
c -> Int
1 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ RobotColumn -> Int
colWidth RobotColumn
c
emptyRobotDisplay :: Set DebugOption -> RobotDisplay
emptyRobotDisplay :: Set DebugOption -> RobotDisplay
emptyRobotDisplay Set DebugOption
opt =
RobotDisplay
{ _isDetailsOpened :: Bool
_isDetailsOpened = Bool
False
,
_robotsGridList :: GridTabularList Name Int
_robotsGridList = Name
-> Seq Int
-> ListItemHeight
-> Seq ColWidth
-> GridTabularList Name Int
forall n e.
n -> Seq e -> ListItemHeight -> Seq ColWidth -> GridTabularList n e
BL.gridTabularList (RobotsDisplayMode -> Name
RobotsListDialog RobotsDisplayMode
RobotList) Seq Int
forall a. Monoid a => a
mempty (Int -> ListItemHeight
LstItmH Int
1) (Set DebugOption -> Seq ColWidth
colWidths Set DebugOption
opt)
, _robotDetailsPaneState :: RobotDetailsPaneState
_robotDetailsPaneState =
RobotDetailsPaneState
{ _detailFocus :: FocusRing Name
_detailFocus = [Name] -> FocusRing Name
forall n. [n] -> FocusRing n
focusRing ([Name] -> FocusRing Name) -> [Name] -> FocusRing Name
forall a b. (a -> b) -> a -> b
$ (RobotDetailSubpane -> Name) -> [RobotDetailSubpane] -> [Name]
forall a b. (a -> b) -> [a] -> [b]
map (RobotsDisplayMode -> Name
RobotsListDialog (RobotsDisplayMode -> Name)
-> (RobotDetailSubpane -> RobotsDisplayMode)
-> RobotDetailSubpane
-> Name
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RobotDetailSubpane -> RobotsDisplayMode
SingleRobotDetails) [RobotDetailSubpane]
forall a. (Enum a, Bounded a) => [a]
enumerate
, _logsList :: GenericList Name Seq LogEntry
_logsList = Name -> Seq LogEntry -> Int -> GenericList Name Seq LogEntry
forall (t :: * -> *) n e.
Foldable t =>
n -> t e -> Int -> GenericList n t e
BL.list (RobotsDisplayMode -> Name
RobotsListDialog (RobotsDisplayMode -> Name) -> RobotsDisplayMode -> Name
forall a b. (a -> b) -> a -> b
$ RobotDetailSubpane -> RobotsDisplayMode
SingleRobotDetails RobotDetailSubpane
RobotLogPane) Seq LogEntry
forall a. Monoid a => a
mempty Int
1
, _cmdHistogramList :: List Name (Const, Int)
_cmdHistogramList = Name -> Vector (Const, Int) -> Int -> List Name (Const, Int)
forall (t :: * -> *) n e.
Foldable t =>
n -> t e -> Int -> GenericList n t e
BL.list (RobotsDisplayMode -> Name
RobotsListDialog (RobotsDisplayMode -> Name) -> RobotsDisplayMode -> Name
forall a b. (a -> b) -> a -> b
$ RobotDetailSubpane -> RobotsDisplayMode
SingleRobotDetails RobotDetailSubpane
RobotCommandHistogramPane) Vector (Const, Int)
forall a. Monoid a => a
mempty Int
1
}
}
getSelectedRID :: BL.GridTabularList Name RID -> Maybe RID
getSelectedRID :: GridTabularList Name Int -> Maybe Int
getSelectedRID GridTabularList Name Int
gl = (Int, Int) -> Int
forall a b. (a, b) -> b
snd ((Int, Int) -> Int) -> Maybe (Int, Int) -> Maybe Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenericList Name Seq Int -> Maybe (Int, Int)
forall (t :: * -> *) e n.
(Splittable t, Traversable t, Semigroup (t e)) =>
GenericList n t e -> Maybe (Int, e)
BL.listSelectedElement GridTabularList Name Int
gl.list
getSelectedRobot :: GameState -> BL.GridTabularList Name RID -> Maybe Robot
getSelectedRobot :: GameState -> GridTabularList Name Int -> Maybe Robot
getSelectedRobot GameState
g GridTabularList Name Int
gl = do
Int
rid <- GridTabularList Name Int -> Maybe Int
getSelectedRID GridTabularList Name Int
gl
GameState
g GameState
-> Getting (Maybe Robot) GameState (Maybe Robot) -> Maybe Robot
forall s a. s -> Getting a s a -> a
^. (Robots -> Const (Maybe Robot) Robots)
-> GameState -> Const (Maybe Robot) GameState
Lens' GameState Robots
robotInfo ((Robots -> Const (Maybe Robot) Robots)
-> GameState -> Const (Maybe Robot) GameState)
-> ((Maybe Robot -> Const (Maybe Robot) (Maybe Robot))
-> Robots -> Const (Maybe Robot) Robots)
-> Getting (Maybe Robot) GameState (Maybe Robot)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (IntMap Robot -> Const (Maybe Robot) (IntMap Robot))
-> Robots -> Const (Maybe Robot) Robots
Lens' Robots (IntMap Robot)
robotMap ((IntMap Robot -> Const (Maybe Robot) (IntMap Robot))
-> Robots -> Const (Maybe Robot) Robots)
-> ((Maybe Robot -> Const (Maybe Robot) (Maybe Robot))
-> IntMap Robot -> Const (Maybe Robot) (IntMap Robot))
-> (Maybe Robot -> Const (Maybe Robot) (Maybe Robot))
-> Robots
-> Const (Maybe Robot) Robots
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Index (IntMap Robot)
-> Lens' (IntMap Robot) (Maybe (IxValue (IntMap Robot)))
forall m. At m => Index m -> Lens' m (Maybe (IxValue m))
at Int
Index (IntMap Robot)
rid
updateRobotList :: Set DebugOption -> GameState -> BL.GridTabularList Name RID -> BL.GridTabularList Name RID
updateRobotList :: Set DebugOption
-> GameState
-> GridTabularList Name Int
-> GridTabularList Name Int
updateRobotList Set DebugOption
dOpts GameState
g GridTabularList Name Int
l = GridTabularList Name Int
l {BL.list = updatedList}
where
updatedList :: BL.GenericList Name Seq RID
updatedList :: GenericList Name Seq Int
updatedList = Seq Int
-> Maybe Int
-> GenericList Name Seq Int
-> GenericList Name Seq Int
forall (t :: * -> *) e n.
(Foldable t, Splittable t) =>
t e -> Maybe Int -> GenericList n t e -> GenericList n t e
BL.listReplace Seq Int
rids Maybe Int
sel GridTabularList Name Int
l.list
rids :: Seq RID
rids :: Seq Int
rids = [Int] -> Seq Int
forall a. [a] -> Seq a
S.fromList ([Int] -> Seq Int) -> ([Robot] -> [Int]) -> [Robot] -> Seq Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Robot -> Int) -> [Robot] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Getting Int Robot Int -> Robot -> Int
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Int Robot Int
Getter Robot Int
robotID) ([Robot] -> Seq Int) -> [Robot] -> Seq Int
forall a b. (a -> b) -> a -> b
$ [Robot]
robots
sel :: Maybe Int
sel :: Maybe Int
sel = (Int -> Seq Int -> Maybe Int) -> Seq Int -> Int -> Maybe Int
forall a b c. (a -> b -> c) -> b -> a -> c
flip Int -> Seq Int -> Maybe Int
forall a. Eq a => a -> Seq a -> Maybe Int
S.elemIndexL Seq Int
rids (Int -> Maybe Int) -> Maybe Int -> Maybe Int
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< GridTabularList Name Int -> Maybe Int
getSelectedRID GridTabularList Name Int
l
robots :: [Robot]
robots :: [Robot]
robots = GameState
g GameState -> Getting [Robot] GameState [Robot] -> [Robot]
forall s a. s -> Getting a s a -> a
^. (Robots -> Const [Robot] Robots)
-> GameState -> Const [Robot] GameState
Lens' GameState Robots
robotInfo ((Robots -> Const [Robot] Robots)
-> GameState -> Const [Robot] GameState)
-> (([Robot] -> Const [Robot] [Robot])
-> Robots -> Const [Robot] Robots)
-> Getting [Robot] GameState [Robot]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (IntMap Robot -> Const [Robot] (IntMap Robot))
-> Robots -> Const [Robot] Robots
Lens' Robots (IntMap Robot)
robotMap ((IntMap Robot -> Const [Robot] (IntMap Robot))
-> Robots -> Const [Robot] Robots)
-> (([Robot] -> Const [Robot] [Robot])
-> IntMap Robot -> Const [Robot] (IntMap Robot))
-> ([Robot] -> Const [Robot] [Robot])
-> Robots
-> Const [Robot] Robots
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (IntMap Robot -> [Robot])
-> ([Robot] -> Const [Robot] [Robot])
-> IntMap Robot
-> Const [Robot] (IntMap Robot)
forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
to IntMap Robot -> [Robot]
forall a. IntMap a -> [a]
IM.elems (([Robot] -> Const [Robot] [Robot])
-> IntMap Robot -> Const [Robot] (IntMap Robot))
-> (([Robot] -> Const [Robot] [Robot])
-> [Robot] -> Const [Robot] [Robot])
-> ([Robot] -> Const [Robot] [Robot])
-> IntMap Robot
-> Const [Robot] (IntMap Robot)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([Robot] -> [Robot])
-> ([Robot] -> Const [Robot] [Robot])
-> [Robot]
-> Const [Robot] [Robot]
forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
to [Robot] -> [Robot]
filterRobots
filterRobots :: [Robot] -> [Robot]
filterRobots :: [Robot] -> [Robot]
filterRobots = if DebugOption -> Set DebugOption -> Bool
forall a. Ord a => a -> Set a -> Bool
Set.member DebugOption
ListAllRobots Set DebugOption
dOpts then [Robot] -> [Robot]
forall a. a -> a
id else (Robot -> Bool) -> [Robot] -> [Robot]
forall a. (a -> Bool) -> [a] -> [a]
filter (\Robot
r -> Robot -> Bool
isRelevant Robot
r Bool -> Bool -> Bool
&& Robot -> Bool
isNear Robot
r)
basePos :: Point V2 Double
basePos :: Point V2 Double
basePos = Int32 -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac (Int32 -> Double) -> Point V2 Int32 -> Point V2 Double
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Point V2 Int32 -> Maybe (Point V2 Int32) -> Point V2 Int32
forall a. a -> Maybe a -> a
fromMaybe Point V2 Int32
forall (f :: * -> *) a. (Additive f, Num a) => Point f a
origin (GameState
g GameState
-> Getting (First (Point V2 Int32)) GameState (Point V2 Int32)
-> Maybe (Point V2 Int32)
forall s a. s -> Getting (First a) s a -> Maybe a
^? (Robot -> Const (First (Point V2 Int32)) Robot)
-> GameState -> Const (First (Point V2 Int32)) GameState
Traversal' GameState Robot
baseRobot ((Robot -> Const (First (Point V2 Int32)) Robot)
-> GameState -> Const (First (Point V2 Int32)) GameState)
-> ((Point V2 Int32
-> Const (First (Point V2 Int32)) (Point V2 Int32))
-> Robot -> Const (First (Point V2 Int32)) Robot)
-> Getting (First (Point V2 Int32)) GameState (Point V2 Int32)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Cosmic (Point V2 Int32)
-> Const (First (Point V2 Int32)) (Cosmic (Point V2 Int32)))
-> Robot -> Const (First (Point V2 Int32)) Robot
Getter Robot (Cosmic (Point V2 Int32))
robotLocation ((Cosmic (Point V2 Int32)
-> Const (First (Point V2 Int32)) (Cosmic (Point V2 Int32)))
-> Robot -> Const (First (Point V2 Int32)) Robot)
-> ((Point V2 Int32
-> Const (First (Point V2 Int32)) (Point V2 Int32))
-> Cosmic (Point V2 Int32)
-> Const (First (Point V2 Int32)) (Cosmic (Point V2 Int32)))
-> (Point V2 Int32
-> Const (First (Point V2 Int32)) (Point V2 Int32))
-> Robot
-> Const (First (Point V2 Int32)) Robot
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Point V2 Int32 -> Const (First (Point V2 Int32)) (Point V2 Int32))
-> Cosmic (Point V2 Int32)
-> Const (First (Point V2 Int32)) (Cosmic (Point V2 Int32))
forall a1 a2 (f :: * -> *).
Functor f =>
(a1 -> f a2) -> Cosmic a1 -> f (Cosmic a2)
planar)
isRelevant :: Robot -> Bool
isRelevant Robot
r = Robot
r Robot -> Getting Int Robot Int -> Int
forall s a. s -> Getting a s a -> a
^. Getting Int Robot Int
Getter Robot Int
robotID Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 Bool -> Bool -> Bool
|| Bool -> Bool
not (Robot
r Robot -> Getting Bool Robot Bool -> Bool
forall s a. s -> Getting a s a -> a
^. Getting Bool Robot Bool
Lens' Robot Bool
systemRobot)
isNear :: Robot -> Bool
isNear Robot
r = Bool
creative Bool -> Bool -> Bool
|| Point V2 Double -> Point V2 Double -> Double
forall a. Floating a => Point V2 a -> Point V2 a -> a
forall (f :: * -> *) a. (Metric f, Floating a) => f a -> f a -> a
distance (Int32 -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac (Int32 -> Double) -> Point V2 Int32 -> Point V2 Double
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Robot
r Robot
-> Getting (Point V2 Int32) Robot (Point V2 Int32)
-> Point V2 Int32
forall s a. s -> Getting a s a -> a
^. (Cosmic (Point V2 Int32)
-> Const (Point V2 Int32) (Cosmic (Point V2 Int32)))
-> Robot -> Const (Point V2 Int32) Robot
Getter Robot (Cosmic (Point V2 Int32))
robotLocation ((Cosmic (Point V2 Int32)
-> Const (Point V2 Int32) (Cosmic (Point V2 Int32)))
-> Robot -> Const (Point V2 Int32) Robot)
-> ((Point V2 Int32 -> Const (Point V2 Int32) (Point V2 Int32))
-> Cosmic (Point V2 Int32)
-> Const (Point V2 Int32) (Cosmic (Point V2 Int32)))
-> Getting (Point V2 Int32) Robot (Point V2 Int32)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Point V2 Int32 -> Const (Point V2 Int32) (Point V2 Int32))
-> Cosmic (Point V2 Int32)
-> Const (Point V2 Int32) (Cosmic (Point V2 Int32))
forall a1 a2 (f :: * -> *).
Functor f =>
(a1 -> f a2) -> Cosmic a1 -> f (Cosmic a2)
planar) Point V2 Double
basePos Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
< Double
32
creative :: Bool
creative = GameState
g GameState -> Getting Bool GameState Bool -> Bool
forall s a. s -> Getting a s a -> a
^. Getting Bool GameState Bool
Lens' GameState Bool
creativeMode
columnHdrAttr :: AttrName
columnHdrAttr :: AttrName
columnHdrAttr = String -> AttrName
attrName String
"columnHeader"
rowHdrAttr :: AttrName
rowHdrAttr :: AttrName
rowHdrAttr = String -> AttrName
attrName String
"rowHeader"
drawRobotsDisplayModal :: UIGameplay -> GameState -> RobotDisplay -> Widget Name
drawRobotsDisplayModal :: UIGameplay -> GameState -> RobotDisplay -> Widget Name
drawRobotsDisplayModal UIGameplay
t GameState
g RobotDisplay
robDisplay =
if RobotDisplay
robDisplay RobotDisplay -> Getting Bool RobotDisplay Bool -> Bool
forall s a. s -> Getting a s a -> a
^. Getting Bool RobotDisplay Bool
Lens' RobotDisplay Bool
isDetailsOpened
then Widget Name
robDetail
else Widget Name
robList
where
robDetail :: Widget Name
robDetail :: Widget Name
robDetail =
let detailsContent :: Widget Name
detailsContent = case GameState -> GridTabularList Name Int -> Maybe Robot
getSelectedRobot GameState
g (RobotDisplay
robDisplay RobotDisplay
-> Getting
(GridTabularList Name Int) RobotDisplay (GridTabularList Name Int)
-> GridTabularList Name Int
forall s a. s -> Getting a s a -> a
^. Getting
(GridTabularList Name Int) RobotDisplay (GridTabularList Name Int)
Lens' RobotDisplay (GridTabularList Name Int)
robotsGridList) of
Maybe Robot
Nothing -> String -> Widget Name
forall n. String -> Widget n
str String
"No selection"
Just Robot
r -> Robot -> RobotDetailsPaneState -> Widget Name
renderRobotDetails Robot
r (RobotDetailsPaneState -> Widget Name)
-> RobotDetailsPaneState -> Widget Name
forall a b. (a -> b) -> a -> b
$ RobotDisplay
robDisplay RobotDisplay
-> Getting RobotDetailsPaneState RobotDisplay RobotDetailsPaneState
-> RobotDetailsPaneState
forall s a. s -> Getting a s a -> a
^. Getting RobotDetailsPaneState RobotDisplay RobotDetailsPaneState
Lens' RobotDisplay RobotDetailsPaneState
robotDetailsPaneState
in [Widget Name] -> Widget Name
forall n. [Widget n] -> Widget n
vBox
[ Widget Name
detailsContent
, Widget Name
forall n. Widget n
tabControlFooter
]
robList :: Widget Name
robList :: Widget Name
robList = UIGameplay -> GameState -> GridTabularList Name Int -> Widget Name
drawRobotsList UIGameplay
t GameState
g (GridTabularList Name Int -> Widget Name)
-> GridTabularList Name Int -> Widget Name
forall a b. (a -> b) -> a -> b
$ RobotDisplay
robDisplay RobotDisplay
-> Getting
(GridTabularList Name Int) RobotDisplay (GridTabularList Name Int)
-> GridTabularList Name Int
forall s a. s -> Getting a s a -> a
^. Getting
(GridTabularList Name Int) RobotDisplay (GridTabularList Name Int)
Lens' RobotDisplay (GridTabularList Name Int)
robotsGridList
drawRobotsList :: UIGameplay -> GameState -> BL.GridTabularList Name RID -> Widget Name
drawRobotsList :: UIGameplay -> GameState -> GridTabularList Name Int -> Widget Name
drawRobotsList UIGameplay
t GameState
g = Int -> Widget Name -> Widget Name
forall n. Int -> Widget n -> Widget n
vLimit Int
30 (Widget Name -> Widget Name)
-> (GridTabularList Name Int -> Widget Name)
-> GridTabularList Name Int
-> Widget Name
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GridRenderers Name Int
-> ListFocused -> GridTabularList Name Int -> Widget Name
forall n e.
(Ord n, Show n) =>
GridRenderers n e -> ListFocused -> GridTabularList n e -> Widget n
BL.renderGridTabularList (UIGameplay -> GameState -> GridRenderers Name Int
robotGridRenderers UIGameplay
t GameState
g) (Bool -> ListFocused
LstFcs Bool
True)
robotGridRenderers :: UIGameplay -> GameState -> BL.GridRenderers Name RID
robotGridRenderers :: UIGameplay -> GameState -> GridRenderers Name Int
robotGridRenderers UIGameplay
t GameState
g =
BL.GridRenderers
{ cell :: ListFocused -> WidthDeficit -> GridCtxt -> Int -> Widget Name
BL.cell = UIGameplay
-> GameState
-> ListFocused
-> WidthDeficit
-> GridCtxt
-> Int
-> Widget Name
drawRobotGridCell UIGameplay
t GameState
g
, rowHdr :: Maybe (RowHdr Name Int)
BL.rowHdr = RowHdr Name Int -> Maybe (RowHdr Name Int)
forall a. a -> Maybe a
Just RowHdr Name Int
forall a. RowHdr Name a
rowHdr
, colHdr :: Maybe (GridColHdr Name)
BL.colHdr = GridColHdr Name -> Maybe (GridColHdr Name)
forall a. a -> Maybe a
Just GridColHdr Name
colHdr
, colHdrRowHdr :: Maybe (ColHdrRowHdr Name)
BL.colHdrRowHdr = ColHdrRowHdr Name -> Maybe (ColHdrRowHdr Name)
forall a. a -> Maybe a
Just ColHdrRowHdr Name
colRowHdr
}
rowHdr :: RowHdr Name a
rowHdr :: forall a. RowHdr Name a
rowHdr =
RowHdr
{ draw :: ListFocused -> WidthDeficit -> RowHdrCtxt -> Int -> Widget Name
draw = \ListFocused
_ (WdthD Int
wd) (RowHdrCtxt (Sel Bool
s)) Int
rh ->
let attrFn :: Widget n -> Widget n
attrFn = Bool -> (Widget n -> Widget n) -> Widget n -> Widget n
forall a. Bool -> (a -> a) -> a -> a
applyWhen (Bool -> Bool
not Bool
s) ((Widget n -> Widget n) -> Widget n -> Widget n)
-> (Widget n -> Widget n) -> Widget n -> Widget n
forall a b. (a -> b) -> a -> b
$ AttrName -> Widget n -> Widget n
forall n. AttrName -> Widget n -> Widget n
withAttr AttrName
rowHdrAttr
in Widget Name -> Widget Name
forall {n}. Widget n -> Widget n
attrFn (Widget Name -> Widget Name) -> Widget Name -> Widget Name
forall a b. (a -> b) -> a -> b
$ Padding -> Widget Name -> Widget Name
forall n. Padding -> Widget n -> Widget n
padRight (Int -> Padding
Pad (Int -> Padding) -> Int -> Padding
forall a b. (a -> b) -> a -> b
$ if Int
wd Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0 then Int
0 else Int
1) (Widget Name -> Widget Name) -> Widget Name -> Widget Name
forall a b. (a -> b) -> a -> b
$ Padding -> Widget Name -> Widget Name
forall n. Padding -> Widget n -> Widget n
padLeft Padding
Max (String -> Widget Name
forall n. String -> Widget n
str (String -> Widget Name) -> String -> Widget Name
forall a b. (a -> b) -> a -> b
$ Int -> String
forall a. Show a => a -> String
show Int
rh)
, width :: AvailWidth -> [Int] -> RowHdrWidth
width = \AvailWidth
_ [Int]
rh -> Int -> RowHdrWidth
RowHdrW (Int -> RowHdrWidth) -> ([Int] -> Int) -> [Int] -> RowHdrWidth
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
2) (Int -> Int) -> ([Int] -> Int) -> [Int] -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Int] -> Int
forall a. (Num a, Ord a) => [a] -> a
maximum0 ([Int] -> RowHdrWidth) -> [Int] -> RowHdrWidth
forall a b. (a -> b) -> a -> b
$ (Int -> Int) -> [Int] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map (String -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length (String -> Int) -> (Int -> String) -> Int -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String
forall a. Show a => a -> String
show) [Int]
rh
, toRH :: a -> Index -> Int
toRH = \a
_ (Ix Int
i) -> Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1
}
colHdr :: BL.GridColHdr Name
colHdr :: GridColHdr Name
colHdr =
BL.GridColHdr
{ draw :: ListFocused -> WidthDeficit -> GridColCtxt -> Widget Name
draw =
\ListFocused
_ (WdthD Int
widthDef) (BL.GColC (BL.Ix Int
i) (BL.Sel Bool
_sel)) ->
let colGap :: Widget n -> Widget n
colGap = Padding -> Widget n -> Widget n
forall n. Padding -> Widget n -> Widget n
padLeft (Int -> Padding
Pad (Int -> Padding) -> Int -> Padding
forall a b. (a -> b) -> a -> b
$ if Int
widthDef Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0 then Int
0 else Int
1)
in AttrName -> Widget Name -> Widget Name
forall n. AttrName -> Widget n -> Widget n
withAttr AttrName
columnHdrAttr (Widget Name -> Widget Name
forall {n}. Widget n -> Widget n
colGap (Widget Name -> Widget Name)
-> (RobotColumn -> Widget Name) -> RobotColumn -> Widget Name
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Widget Name
forall n. Text -> Widget n
txt (Text -> Widget Name)
-> (RobotColumn -> Text) -> RobotColumn -> Widget Name
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RobotColumn -> Text
colName (RobotColumn -> Widget Name) -> RobotColumn -> Widget Name
forall a b. (a -> b) -> a -> b
$ Int -> RobotColumn
forall a. Enum a => Int -> a
toEnum Int
i) Widget Name -> Widget Name -> Widget Name
forall n. Widget n -> Widget n -> Widget n
<=> Widget Name
forall n. Widget n
hBorder
, height :: ColHdrHeight
height = Int -> ColHdrHeight
ColHdrH Int
2
}
colRowHdr :: BL.ColHdrRowHdr Name
colRowHdr :: ColHdrRowHdr Name
colRowHdr = (ListFocused -> WidthDeficit -> Widget Name) -> ColHdrRowHdr Name
forall n.
(ListFocused -> WidthDeficit -> Widget n) -> ColHdrRowHdr n
BL.ColHdrRowHdr ((ListFocused -> WidthDeficit -> Widget Name) -> ColHdrRowHdr Name)
-> (ListFocused -> WidthDeficit -> Widget Name)
-> ColHdrRowHdr Name
forall a b. (a -> b) -> a -> b
$ \ListFocused
_ (WdthD Int
_wd) -> Char -> Widget Name
forall n. Char -> Widget n
fill Char
' ' Widget Name -> Widget Name -> Widget Name
forall n. Widget n -> Widget n -> Widget n
<=> Widget Name
forall n. Widget n
hBorder
drawRobotGridCell :: UIGameplay -> GameState -> ListFocused -> WidthDeficit -> BL.GridCtxt -> RID -> Widget Name
drawRobotGridCell :: UIGameplay
-> GameState
-> ListFocused
-> WidthDeficit
-> GridCtxt
-> Int
-> Widget Name
drawRobotGridCell UIGameplay
t GameState
g ListFocused
_foc (WdthD Int
widthDef) GridCtxt
ctx Int
rid =
Widget Name -> Widget Name
forall {n}. Widget n -> Widget n
colGap (Widget Name -> Widget Name)
-> (Widget Name -> Widget Name) -> Widget Name -> Widget Name
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Widget Name -> Widget Name
forall {n}. Widget n -> Widget n
withSelectedAttr (Widget Name -> Widget Name) -> Widget Name -> Widget Name
forall a b. (a -> b) -> a -> b
$
case GameState
g GameState
-> Getting (Maybe Robot) GameState (Maybe Robot) -> Maybe Robot
forall s a. s -> Getting a s a -> a
^. (Robots -> Const (Maybe Robot) Robots)
-> GameState -> Const (Maybe Robot) GameState
Lens' GameState Robots
robotInfo ((Robots -> Const (Maybe Robot) Robots)
-> GameState -> Const (Maybe Robot) GameState)
-> ((Maybe Robot -> Const (Maybe Robot) (Maybe Robot))
-> Robots -> Const (Maybe Robot) Robots)
-> Getting (Maybe Robot) GameState (Maybe Robot)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (IntMap Robot -> Const (Maybe Robot) (IntMap Robot))
-> Robots -> Const (Maybe Robot) Robots
Lens' Robots (IntMap Robot)
robotMap ((IntMap Robot -> Const (Maybe Robot) (IntMap Robot))
-> Robots -> Const (Maybe Robot) Robots)
-> ((Maybe Robot -> Const (Maybe Robot) (Maybe Robot))
-> IntMap Robot -> Const (Maybe Robot) (IntMap Robot))
-> (Maybe Robot -> Const (Maybe Robot) (Maybe Robot))
-> Robots
-> Const (Maybe Robot) Robots
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Index (IntMap Robot)
-> Lens' (IntMap Robot) (Maybe (IxValue (IntMap Robot)))
forall m. At m => Index m -> Lens' m (Maybe (IxValue m))
at Int
Index (IntMap Robot)
rid of
Maybe Robot
Nothing -> case RobotColumn
col of
RobotColumn
ColID -> Padding -> Widget Name -> Widget Name
forall n. Padding -> Widget n -> Widget n
padRight Padding
Max (Widget Name -> Widget Name) -> Widget Name -> Widget Name
forall a b. (a -> b) -> a -> b
$ Int -> Widget Name
forall a. Show a => a -> Widget Name
showW Int
rid
RobotColumn
_ -> Char -> Widget Name
forall n. Char -> Widget n
fill Char
'?'
Just Robot
r -> case RobotColumn
col of
RobotColumn
ColName -> Padding -> Widget Name -> Widget Name
forall n. Padding -> Widget n -> Widget n
padRight Padding
Max (Widget Name -> Widget Name) -> Widget Name -> Widget Name
forall a b. (a -> b) -> a -> b
$ Robot -> Widget Name
nameWidget Robot
r
RobotColumn
ColAge -> Widget Name -> Widget Name
forall {n}. Widget n -> Widget n
hCenter (Widget Name -> Widget Name) -> Widget Name -> Widget Name
forall a b. (a -> b) -> a -> b
$ Robot -> Widget Name
ageWidget Robot
r
RobotColumn
ColPos -> Widget Name -> Widget Name
forall {n}. Widget n -> Widget n
hCenter (Widget Name -> Widget Name) -> Widget Name -> Widget Name
forall a b. (a -> b) -> a -> b
$ Robot -> Widget Name
locWidget Robot
r
RobotColumn
ColItems -> Padding -> Widget Name -> Widget Name
forall n. Padding -> Widget n -> Widget n
padLeft Padding
Max (Widget Name -> Widget Name) -> Widget Name -> Widget Name
forall a b. (a -> b) -> a -> b
$ Robot -> Widget Name
rInvCount Robot
r
RobotColumn
ColStatus -> Widget Name -> Widget Name
forall {n}. Widget n -> Widget n
hCenter (Widget Name -> Widget Name) -> Widget Name -> Widget Name
forall a b. (a -> b) -> a -> b
$ Robot -> Widget Name
statusWidget Robot
r
RobotColumn
ColActns -> Padding -> Widget Name -> Widget Name
forall n. Padding -> Widget n -> Widget n
padLeft Padding
Max (Widget Name -> Widget Name)
-> (Int -> Widget Name) -> Int -> Widget Name
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Widget Name
forall a. Show a => a -> Widget Name
showW (Int -> Widget Name) -> Int -> Widget Name
forall a b. (a -> b) -> a -> b
$ Robot
r Robot -> Getting Int Robot Int -> Int
forall s a. s -> Getting a s a -> a
^. (ActivityCounts -> Const Int ActivityCounts)
-> Robot -> Const Int Robot
Lens' Robot ActivityCounts
activityCounts ((ActivityCounts -> Const Int ActivityCounts)
-> Robot -> Const Int Robot)
-> ((Int -> Const Int Int)
-> ActivityCounts -> Const Int ActivityCounts)
-> Getting Int Robot Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> Const Int Int)
-> ActivityCounts -> Const Int ActivityCounts
Lens' ActivityCounts Int
tangibleCommandCount
RobotColumn
ColCmds -> Padding -> Widget Name -> Widget Name
forall n. Padding -> Widget n -> Widget n
padLeft Padding
Max (Widget Name -> Widget Name)
-> (Map Const Int -> Widget Name) -> Map Const Int -> Widget Name
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Widget Name
forall a. Show a => a -> Widget Name
showW (Int -> Widget Name)
-> (Map Const Int -> Int) -> Map Const Int -> Widget Name
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Int] -> Int
forall a. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum ([Int] -> Int) -> (Map Const Int -> [Int]) -> Map Const Int -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Map Const Int -> [Int]
forall k a. Map k a -> [a]
M.elems (Map Const Int -> Widget Name) -> Map Const Int -> Widget Name
forall a b. (a -> b) -> a -> b
$ Robot
r Robot
-> Getting (Map Const Int) Robot (Map Const Int) -> Map Const Int
forall s a. s -> Getting a s a -> a
^. (ActivityCounts -> Const (Map Const Int) ActivityCounts)
-> Robot -> Const (Map Const Int) Robot
Lens' Robot ActivityCounts
activityCounts ((ActivityCounts -> Const (Map Const Int) ActivityCounts)
-> Robot -> Const (Map Const Int) Robot)
-> ((Map Const Int -> Const (Map Const Int) (Map Const Int))
-> ActivityCounts -> Const (Map Const Int) ActivityCounts)
-> Getting (Map Const Int) Robot (Map Const Int)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Map Const Int -> Const (Map Const Int) (Map Const Int))
-> ActivityCounts -> Const (Map Const Int) ActivityCounts
Lens' ActivityCounts (Map Const Int)
commandsHistogram
RobotColumn
ColCycles -> Padding -> Widget Name -> Widget Name
forall n. Padding -> Widget n -> Widget n
padLeft Padding
Max (Widget Name -> Widget Name)
-> (Int -> Widget Name) -> Int -> Widget Name
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Widget Name
forall a. Show a => a -> Widget Name
showW (Int -> Widget Name) -> Int -> Widget Name
forall a b. (a -> b) -> a -> b
$ Robot
r Robot -> Getting Int Robot Int -> Int
forall s a. s -> Getting a s a -> a
^. (ActivityCounts -> Const Int ActivityCounts)
-> Robot -> Const Int Robot
Lens' Robot ActivityCounts
activityCounts ((ActivityCounts -> Const Int ActivityCounts)
-> Robot -> Const Int Robot)
-> ((Int -> Const Int Int)
-> ActivityCounts -> Const Int ActivityCounts)
-> Getting Int Robot Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> Const Int Int)
-> ActivityCounts -> Const Int ActivityCounts
Lens' ActivityCounts Int
lifetimeStepCount
RobotColumn
ColActivity -> Padding -> Widget Name -> Widget Name
forall n. Padding -> Widget n -> Widget n
padLeft Padding
Max (Widget Name -> Widget Name) -> Widget Name -> Widget Name
forall a b. (a -> b) -> a -> b
$ TemporalState -> Robot -> Widget Name
renderDutyCycle (GameState
g GameState
-> Getting TemporalState GameState TemporalState -> TemporalState
forall s a. s -> Getting a s a -> a
^. Getting TemporalState GameState TemporalState
Lens' GameState TemporalState
temporal) Robot
r
RobotColumn
ColLog -> Widget Name -> Widget Name
forall {n}. Widget n -> Widget n
hCenter (Widget Name -> Widget Name) -> Widget Name -> Widget Name
forall a b. (a -> b) -> a -> b
$ Robot -> Widget Name
rLog Robot
r
RobotColumn
ColID -> Padding -> Widget Name -> Widget Name
forall n. Padding -> Widget n -> Widget n
padRight Padding
Max (Widget Name -> Widget Name) -> Widget Name -> Widget Name
forall a b. (a -> b) -> a -> b
$ Int -> Widget Name
forall a. Show a => a -> Widget Name
showW Int
rid
where
(BL.GColC (BL.Ix Int
cIx) (BL.Sel Bool
cSel)) = GridCtxt
ctx.col
(BL.GRowC (BL.Ix Int
_ix) (BL.Sel Bool
rSel)) = GridCtxt
ctx.row
withSelectedAttr :: Widget n -> Widget n
withSelectedAttr = if Bool
cSel Bool -> Bool -> Bool
&& Bool
rSel then AttrName -> Widget n -> Widget n
forall n. AttrName -> Widget n -> Widget n
withAttr AttrName
BL.listSelectedAttr else Widget n -> Widget n
forall a. a -> a
id
col :: RobotColumn
col :: RobotColumn
col = if Int
cIx Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= RobotColumn -> Int
forall a. Enum a => a -> Int
fromEnum (RobotColumn
forall a. Bounded a => a
maxBound :: RobotColumn) then Int -> RobotColumn
forall a. Enum a => Int -> a
toEnum Int
cIx else RobotColumn
ColLog
showW :: Show a => a -> Widget Name
showW :: forall a. Show a => a -> Widget Name
showW = String -> Widget Name
forall n. String -> Widget n
str (String -> Widget Name) -> (a -> String) -> a -> Widget Name
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> String
forall a. Show a => a -> String
show
highlightSystem :: Robot -> Widget Name -> Widget Name
highlightSystem :: Robot -> Widget Name -> Widget Name
highlightSystem Robot
r = Bool -> (Widget Name -> Widget Name) -> Widget Name -> Widget Name
forall a. Bool -> (a -> a) -> a -> a
applyWhen (Robot
r Robot -> Getting Bool Robot Bool -> Bool
forall s a. s -> Getting a s a -> a
^. Getting Bool Robot Bool
Lens' Robot Bool
systemRobot) ((Widget Name -> Widget Name) -> Widget Name -> Widget Name)
-> (Widget Name -> Widget Name) -> Widget Name -> Widget Name
forall a b. (a -> b) -> a -> b
$ AttrName -> Widget Name -> Widget Name
forall n. AttrName -> Widget n -> Widget n
withAttr AttrName
highlightAttr
colGap :: Widget n -> Widget n
colGap = Padding -> Widget n -> Widget n
forall n. Padding -> Widget n -> Widget n
padLeft (Int -> Padding
Pad (Int -> Padding) -> Int -> Padding
forall a b. (a -> b) -> a -> b
$ if Int
widthDef Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0 then Int
0 else Int
1)
nameWidget :: Robot -> Widget Name
nameWidget :: Robot -> Widget Name
nameWidget Robot
r =
[Widget Name] -> Widget Name
forall n. [Widget n] -> Widget n
hBox
[ Display -> Widget Name
forall n. Display -> Widget n
renderDisplay (Robot
r Robot -> Getting Display Robot Display -> Display
forall s a. s -> Getting a s a -> a
^. Getting Display Robot Display
Lens' Robot Display
robotDisplay)
, Robot -> Widget Name -> Widget Name
highlightSystem Robot
r (Widget Name -> Widget Name)
-> (Text -> Widget Name) -> Text -> Widget Name
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Widget Name
forall n. Text -> Widget n
txt (Text -> Widget Name) -> Text -> Widget Name
forall a b. (a -> b) -> a -> b
$ Text
" " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Robot
r Robot -> Getting Text Robot Text -> Text
forall s a. s -> Getting a s a -> a
^. Getting Text Robot Text
Lens' Robot Text
robotName
]
ageWidget :: Robot -> Widget Name
ageWidget :: Robot -> Widget Name
ageWidget Robot
r = String -> Widget Name
forall n. String -> Widget n
str String
ageStr
where
TimeSpec Int64
createdAtSec Int64
_ = Robot
r Robot -> Getting TimeSpec Robot TimeSpec -> TimeSpec
forall s a. s -> Getting a s a -> a
^. Getting TimeSpec Robot TimeSpec
Lens' Robot TimeSpec
robotCreatedAt
TimeSpec Int64
nowSec Int64
_ = UIGameplay
t UIGameplay -> Getting TimeSpec UIGameplay TimeSpec -> TimeSpec
forall s a. s -> Getting a s a -> a
^. (UITiming -> Const TimeSpec UITiming)
-> UIGameplay -> Const TimeSpec UIGameplay
Lens' UIGameplay UITiming
uiTiming ((UITiming -> Const TimeSpec UITiming)
-> UIGameplay -> Const TimeSpec UIGameplay)
-> ((TimeSpec -> Const TimeSpec TimeSpec)
-> UITiming -> Const TimeSpec UITiming)
-> Getting TimeSpec UIGameplay TimeSpec
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (TimeSpec -> Const TimeSpec TimeSpec)
-> UITiming -> Const TimeSpec UITiming
Lens' UITiming TimeSpec
lastFrameTime
age :: Int64
age = Int64
nowSec Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
- Int64
createdAtSec
ageStr :: String
ageStr
| Int64
age Int64 -> Int64 -> Bool
forall a. Ord a => a -> a -> Bool
< Int64
60 = Int64 -> String
forall a. Show a => a -> String
show Int64
age String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
"sec"
| Int64
age Int64 -> Int64 -> Bool
forall a. Ord a => a -> a -> Bool
< Int64
3600 = Int64 -> String
forall a. Show a => a -> String
show (Int64
age Int64 -> Int64 -> Int64
forall a. Integral a => a -> a -> a
`div` Int64
60) String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
"min"
| Int64
age Int64 -> Int64 -> Bool
forall a. Ord a => a -> a -> Bool
< Int64
3600 Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
* Int64
24 = Int64 -> String
forall a. Show a => a -> String
show (Int64
age Int64 -> Int64 -> Int64
forall a. Integral a => a -> a -> a
`div` Int64
3600) String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
"hour"
| Bool
otherwise = Int64 -> String
forall a. Show a => a -> String
show (Int64
age Int64 -> Int64 -> Int64
forall a. Integral a => a -> a -> a
`div` Int64
3600 Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
* Int64
24) String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
"day"
rInvCount :: Robot -> Widget Name
rInvCount :: Robot -> Widget Name
rInvCount Robot
r = Int -> Widget Name
forall a. Show a => a -> Widget Name
showW (Int -> Widget Name)
-> (Inventory -> Int) -> Inventory -> Widget Name
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Int] -> Int
forall a. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum ([Int] -> Int) -> (Inventory -> [Int]) -> Inventory -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Int, Entity) -> Int) -> [(Int, Entity)] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map (Int, Entity) -> Int
forall a b. (a, b) -> a
fst ([(Int, Entity)] -> [Int])
-> (Inventory -> [(Int, Entity)]) -> Inventory -> [Int]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Inventory -> [(Int, Entity)]
E.elems (Inventory -> Widget Name) -> Inventory -> Widget Name
forall a b. (a -> b) -> a -> b
$ Robot
r Robot -> Getting Inventory Robot Inventory -> Inventory
forall s a. s -> Getting a s a -> a
^. (Entity -> Const Inventory Entity)
-> Robot -> Const Inventory Robot
forall (phase :: RobotPhase) (f :: * -> *).
Functor f =>
(Entity -> f Entity) -> RobotR phase -> f (RobotR phase)
robotEntity ((Entity -> Const Inventory Entity)
-> Robot -> Const Inventory Robot)
-> ((Inventory -> Const Inventory Inventory)
-> Entity -> Const Inventory Entity)
-> Getting Inventory Robot Inventory
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Inventory -> Const Inventory Inventory)
-> Entity -> Const Inventory Entity
Lens' Entity Inventory
entityInventory
rLog :: Robot -> Widget Name
rLog :: Robot -> Widget Name
rLog Robot
r = String -> Widget Name
forall n. String -> Widget n
str (String -> Widget Name) -> String -> Widget Name
forall a b. (a -> b) -> a -> b
$ if Robot
r Robot -> Getting Bool Robot Bool -> Bool
forall s a. s -> Getting a s a -> a
^. Getting Bool Robot Bool
Lens' Robot Bool
robotLogUpdated then String
"x" else String
" "
locWidget :: Robot -> Widget Name
locWidget :: Robot -> Widget Name
locWidget Robot
r = [Widget Name] -> Widget Name
forall n. [Widget n] -> Widget n
hBox [Widget Name
worldCell, String -> Widget Name
forall n. String -> Widget n
str (String -> Widget Name) -> String -> Widget Name
forall a b. (a -> b) -> a -> b
$ String
" " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
locStr]
where
rCoords :: Cosmic Coords
rCoords = (Point V2 Int32 -> Coords)
-> Cosmic (Point V2 Int32) -> Cosmic Coords
forall a b. (a -> b) -> Cosmic a -> Cosmic b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Point V2 Int32 -> Coords
locToCoords Cosmic (Point V2 Int32)
rLoc
rLoc :: Cosmic (Point V2 Int32)
rLoc = Robot
r Robot
-> Getting
(Cosmic (Point V2 Int32)) Robot (Cosmic (Point V2 Int32))
-> Cosmic (Point V2 Int32)
forall s a. s -> Getting a s a -> a
^. Getting (Cosmic (Point V2 Int32)) Robot (Cosmic (Point V2 Int32))
Getter Robot (Cosmic (Point V2 Int32))
robotLocation
worldCell :: Widget Name
worldCell = UIGameplay -> GameState -> Cosmic Coords -> Widget Name
drawLoc UIGameplay
t GameState
g Cosmic Coords
rCoords
locStr :: String
locStr = Cosmic (Point V2 Int32) -> String
renderCoordsString Cosmic (Point V2 Int32)
rLoc
statusWidget :: Robot -> Widget Name
statusWidget :: Robot -> Widget Name
statusWidget Robot
r = case Robot
r Robot -> Getting CESK Robot CESK -> CESK
forall s a. s -> Getting a s a -> a
^. Getting CESK Robot CESK
Lens' Robot CESK
machine of
Waiting {} -> String -> Widget Name
forall n. String -> Widget n
str String
"waiting"
CESK
_ | Robot -> Bool
isActive Robot
r -> AttrName -> Widget Name -> Widget Name
forall n. AttrName -> Widget n -> Widget n
withAttr AttrName
notifAttr (Widget Name -> Widget Name) -> Widget Name -> Widget Name
forall a b. (a -> b) -> a -> b
$ String -> Widget Name
forall n. String -> Widget n
str String
"busy"
CESK
_ | Bool
otherwise -> AttrName -> Widget Name -> Widget Name
forall n. AttrName -> Widget n -> Widget n
withAttr AttrName
greenAttr (Widget Name -> Widget Name) -> Widget Name -> Widget Name
forall a b. (a -> b) -> a -> b
$ String -> Widget Name
forall n. String -> Widget n
str String
"idle"
renderDutyCycle :: TemporalState -> Robot -> Widget Name
renderDutyCycle :: TemporalState -> Robot -> Widget Name
renderDutyCycle TemporalState
temporalState Robot
r = AttrName -> Widget Name -> Widget Name
forall n. AttrName -> Widget n -> Widget n
withAttr AttrName
dutyCycleAttr (Widget Name -> Widget Name) -> Widget Name -> Widget Name
forall a b. (a -> b) -> a -> b
$ String -> Widget Name
forall n. String -> Widget n
str String
tx
where
tx :: String
tx = Maybe Int -> Double -> ShowS
forall a. RealFloat a => Maybe Int -> a -> ShowS
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
1) Double
dutyCyclePercentage String
"%"
curTicks :: TickNumber
curTicks = TemporalState
temporalState TemporalState
-> Getting TickNumber TemporalState TickNumber -> TickNumber
forall s a. s -> Getting a s a -> a
^. Getting TickNumber TemporalState TickNumber
Lens' TemporalState TickNumber
ticks
window :: WindowedCounter TickNumber
window = Robot
r Robot
-> Getting
(WindowedCounter TickNumber) Robot (WindowedCounter TickNumber)
-> WindowedCounter TickNumber
forall s a. s -> Getting a s a -> a
^. (ActivityCounts
-> Const (WindowedCounter TickNumber) ActivityCounts)
-> Robot -> Const (WindowedCounter TickNumber) Robot
Lens' Robot ActivityCounts
activityCounts ((ActivityCounts
-> Const (WindowedCounter TickNumber) ActivityCounts)
-> Robot -> Const (WindowedCounter TickNumber) Robot)
-> ((WindowedCounter TickNumber
-> Const (WindowedCounter TickNumber) (WindowedCounter TickNumber))
-> ActivityCounts
-> Const (WindowedCounter TickNumber) ActivityCounts)
-> Getting
(WindowedCounter TickNumber) Robot (WindowedCounter TickNumber)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (WindowedCounter TickNumber
-> Const (WindowedCounter TickNumber) (WindowedCounter TickNumber))
-> ActivityCounts
-> Const (WindowedCounter TickNumber) ActivityCounts
Lens' ActivityCounts (WindowedCounter TickNumber)
activityWindow
latestRobotTick :: TickNumber
latestRobotTick = Int -> TickNumber -> TickNumber
addTicks (-Int
1) TickNumber
curTicks
dutyCycleRatio :: UnitInterval Double
dutyCycleRatio = TickNumber -> WindowedCounter TickNumber -> UnitInterval Double
forall a.
(Ord a, Offsettable a) =>
a -> WindowedCounter a -> UnitInterval Double
WC.getOccupancy TickNumber
latestRobotTick WindowedCounter TickNumber
window
dutyCycleAttr :: AttrName
dutyCycleAttr = UnitInterval Double -> NonEmpty AttrName -> AttrName
forall a b. RealFrac a => UnitInterval a -> NonEmpty b -> b
safeIndex UnitInterval Double
dutyCycleRatio NonEmpty AttrName
meterAttributeNames
dutyCyclePercentage :: Double
dutyCyclePercentage :: Double
dutyCyclePercentage = Double
100 Double -> Double -> Double
forall a. Num a => a -> a -> a
* UnitInterval Double -> Double
forall a. UnitInterval a -> a
getValue UnitInterval Double
dutyCycleRatio