Skip to content

Commit

Permalink
implement background passthrough
Browse files Browse the repository at this point in the history
  • Loading branch information
kostmo committed Dec 19, 2023
1 parent 7ae6701 commit e514d06
Showing 1 changed file with 48 additions and 6 deletions.
54 changes: 48 additions & 6 deletions src/Swarm/TUI/View/CellDisplay.hs
Original file line number Diff line number Diff line change
Expand Up @@ -9,6 +9,7 @@ module Swarm.TUI.View.CellDisplay where
import Brick
import Control.Applicative ((<|>))
import Control.Lens (to, view, (&), (.~), (^.))
import Control.Monad (guard)
import Data.ByteString (ByteString)
import Data.Hash.Murmur
import Data.List.NonEmpty qualified as NE
Expand All @@ -32,11 +33,13 @@ import Swarm.Game.Display (
displayObscured,
displayPriority,
hidden,
invisible,
)
import Swarm.Game.Entity
import Swarm.Game.Entity.Cosmetic
import Swarm.Game.Entity.Cosmetic.Assignment (terrainAttributes)
import Swarm.Game.Robot
import Swarm.Game.Scenario (scenarioCosmetics)
import Swarm.Game.Scenario.Topography.Cell (PCell (..))
import Swarm.Game.Scenario.Topography.EntityFacade
import Swarm.Game.Scenario.Topography.Structure.Recognition (foundStructures)
Expand All @@ -54,7 +57,7 @@ import Swarm.TUI.Model.Name
import Swarm.TUI.Model.UI
import Swarm.TUI.View.Attribute.Attr
import Swarm.Util (applyWhen)
import Swarm.Util.Erasable (erasableToMaybe)
import Swarm.Util.Erasable (erasableToMaybe, maybeToErasable)
import Witch (from)
import Witch.Encoding qualified as Encoding

Expand All @@ -79,11 +82,36 @@ drawLoc :: UIState -> GameState -> Cosmic W.Coords -> Widget Name
drawLoc ui g cCoords@(Cosmic _ coords) =
if shouldHideWorldCell ui coords
then str " "
else boldStructure drawCell
else boldStructure $ passthroughRobotBackground drawCell
where
showRobots = ui ^. uiShowRobots
we = ui ^. uiWorldEditor . worldOverdraw
drawCell = renderDisplay $ displayLoc showRobots we g cCoords

(combinedDisplay, maybeRoboDisplay) = displayLoc showRobots we g cCoords
drawCell = renderDisplay combinedDisplay

passthroughRobotBackground =
case maybeBg of
Just c -> modifyDefAttr (`V.withBackColor` c)
Nothing -> id
where
maybeBg = do
guard $ not $ null maybeRoboDisplay
maybeBgColor

mycell =
Cell
terrain
(toFacade <$> maybeToErasable erasableEntity)
[]
where
(terrain, erasableEntity) = EU.getEditorContentAt we worlds cCoords
worlds = view (landscape . multiWorld) g

maybeBgColor = do
(myScenario, _) <- ui ^. scenarioRef
hifi <- getTerrainEntityColor (myScenario ^. scenarioCosmetics) mycell
getBackground $ fmap mkBrickColor hifi

boldStructure = applyWhen isStructure $ modifyDefAttr (`V.withStyle` V.bold)
where
Expand Down Expand Up @@ -163,12 +191,26 @@ displayEntityCell worldEditor ri coords =
-- 'Display's for the terrain, entity, and robots at the location, and
-- taking into account "static" based on the distance to the robot
-- being @view@ed.
displayLoc :: Bool -> WorldOverdraw -> GameState -> Cosmic W.Coords -> Display
displayLoc ::
-- | Should show robots
Bool ->
WorldOverdraw ->
GameState ->
Cosmic W.Coords ->
(Display, Maybe Display)
displayLoc showRobots we g cCoords@(Cosmic _ coords) =
staticDisplay g coords
<> displayLocRaw we ri robots cCoords
(combined, maybeRobotAttribute)
where
combined =
staticDisplay g coords
<> displayLocRaw we ri robots cCoords

ri = RenderingInput (g ^. landscape . multiWorld) (getEntityIsKnown $ mkEntityKnowledge g)

maybeRobotAttribute = do
guard $ not $ combined ^. displayObscured
sconcat <$> NE.nonEmpty (filter (not . view invisible) robots)

robots =
if showRobots
then displayRobotCell g cCoords
Expand Down

0 comments on commit e514d06

Please sign in to comment.