Skip to content

Commit

Permalink
pixijs
Browse files Browse the repository at this point in the history
  • Loading branch information
kostmo committed Dec 18, 2023
1 parent c48a46c commit 253e3a4
Show file tree
Hide file tree
Showing 12 changed files with 286 additions and 30 deletions.
7 changes: 5 additions & 2 deletions src/Swarm/Game/Scenario/Topography/Center.hs
Original file line number Diff line number Diff line change
Expand Up @@ -15,11 +15,14 @@ import Swarm.Game.Scenario (Scenario)
import Swarm.Game.State (SubworldDescription, genRobotTemplates)
import Swarm.Game.Universe (Cosmic (..), SubworldName (DefaultRootSubworld))

determineViewCenter ::
-- | Determine view center for a static map
-- without reference to a 'GameState'
-- (i.e. outside the context of an active game)
determineStaticViewCenter ::
Scenario ->
NonEmpty SubworldDescription ->
Cosmic Location
determineViewCenter s worldTuples =
determineStaticViewCenter s worldTuples =
fromMaybe defaultVC baseRobotLoc
where
theRobots = genRobotTemplates s worldTuples
Expand Down
62 changes: 36 additions & 26 deletions src/Swarm/Game/World/Render.hs
Original file line number Diff line number Diff line change
Expand Up @@ -19,7 +19,7 @@ import Swarm.Game.Display (defaultChar)
import Swarm.Game.Entity.Cosmetic
import Swarm.Game.Location
import Swarm.Game.ResourceLoading (initNameGenerator, readAppData)
import Swarm.Game.Scenario (Scenario, area, loadStandaloneScenario, scenarioCosmetics, scenarioWorlds, ul, worldName)
import Swarm.Game.Scenario (PWorldDescription, Scenario, area, loadStandaloneScenario, scenarioCosmetics, scenarioWorlds, ul, worldName)
import Swarm.Game.Scenario.Status (seedLaunchParams)
import Swarm.Game.Scenario.Topography.Area
import Swarm.Game.Scenario.Topography.Cell
Expand Down Expand Up @@ -85,43 +85,49 @@ fromHiFi = fmap $ \case
-- those triples are not inputs to the VTY attribute creation.
AnsiColor x -> namedToTriple x

-- | When output size is not explicitly provided on command line,
-- | When output size is not explicitly provided,
-- uses natural map bounds (if a map exists).
getBoundingBox ::
Location ->
PWorldDescription e ->
Maybe AreaDimensions ->
W.BoundsRectangle
getBoundingBox vc scenarioWorld maybeSize =
mkBoundingBox areaDims upperLeftLocation
where
upperLeftLocation =
if null maybeSize && not (isEmpty mapAreaDims)
then ul scenarioWorld
else vc .+^ ((`div` 2) <$> V2 (negate w) h)

mkBoundingBox areaDimens upperLeftLoc =
both W.locToCoords locationBounds
where
lowerRightLocation = upperLeftToBottomRight areaDimens upperLeftLoc
locationBounds = (upperLeftLoc, lowerRightLocation)

worldArea = area scenarioWorld
mapAreaDims = getAreaDimensions worldArea
areaDims@(AreaDimensions w h) =
fromMaybe (AreaDimensions 20 10) $
maybeSize <|> surfaceEmpty isEmpty mapAreaDims

getDisplayGrid ::
Location ->
Scenario ->
GameState ->
Maybe AreaDimensions ->
Grid (PCell EntityFacade)
getDisplayGrid myScenario gs maybeSize =
Grid CellPaintDisplay
getDisplayGrid vc myScenario gs maybeSize =
getMapRectangle
mkFacade
(getContentAt worlds . mkCosmic)
(mkBoundingBox areaDims upperLeftLocation)
(getBoundingBox vc firstScenarioWorld maybeSize)
where
mkCosmic = Cosmic $ worldName firstScenarioWorld

worlds = view (landscape . multiWorld) gs

worldTuples = buildWorldTuples myScenario
vc = determineViewCenter myScenario worldTuples

firstScenarioWorld = NE.head $ view scenarioWorlds myScenario
worldArea = area firstScenarioWorld
mapAreaDims = getAreaDimensions worldArea
areaDims@(AreaDimensions w h) =
fromMaybe (AreaDimensions 20 10) $
maybeSize <|> surfaceEmpty isEmpty mapAreaDims

upperLeftLocation =
if null maybeSize && not (isEmpty mapAreaDims)
then ul firstScenarioWorld
else view planar vc .+^ ((`div` 2) <$> V2 (negate w) h)

mkBoundingBox areaDimens upperLeftLoc =
both W.locToCoords locationBounds
where
lowerRightLocation = upperLeftToBottomRight areaDimens upperLeftLoc
locationBounds = (upperLeftLoc, lowerRightLocation)

getRenderableGrid ::
RenderOpts ->
Expand All @@ -138,7 +144,11 @@ getRenderableGrid (RenderOpts maybeSeed _ _ maybeSize) fp = simpleErrorHandle $
myScenario
(seedLaunchParams maybeSeed)
gsc
return (getDisplayGrid myScenario gs maybeSize, myScenario ^. scenarioCosmetics)
let vc =
view planar $
determineStaticViewCenter myScenario $
buildWorldTuples myScenario
return (getDisplayGrid vc myScenario gs maybeSize, myScenario ^. scenarioCosmetics)

doRenderCmd :: RenderOpts -> FilePath -> IO ()
doRenderCmd opts@(RenderOpts _ asPng _ _) mapPath =
Expand Down
2 changes: 1 addition & 1 deletion src/Swarm/TUI/View.hs
Original file line number Diff line number Diff line change
Expand Up @@ -243,7 +243,7 @@ drawNewGameMenuUI (l :| ls) launchOptions = case displayedFor of
, padTop (Pad 1) table
]
where
vc = determineViewCenter s worldTuples
vc = determineStaticViewCenter s worldTuples

worldTuples = buildWorldTuples s
theWorlds = genMultiWorld worldTuples $ fromMaybe 0 $ s ^. scenarioSeed
Expand Down
32 changes: 32 additions & 0 deletions src/Swarm/Web.hs
Original file line number Diff line number Diff line change
Expand Up @@ -67,6 +67,7 @@ import Swarm.Game.Robot
import Swarm.Game.Scenario.Objective
import Swarm.Game.Scenario.Objective.Graph
import Swarm.Game.Scenario.Objective.WinCheck
import Swarm.Game.Scenario.Topography.Area (AreaDimensions (..))
import Swarm.Game.Scenario.Topography.Structure.Recognition
import Swarm.Game.Scenario.Topography.Structure.Recognition.Log
import Swarm.Game.Scenario.Topography.Structure.Recognition.Registry
Expand All @@ -83,6 +84,7 @@ import Swarm.TUI.Model
import Swarm.TUI.Model.Goal
import Swarm.TUI.Model.UI
import Swarm.Util.RingBuffer
import Swarm.Web.Worldview
import System.Timeout (timeout)
import Text.Read (readEither)
import WaiAppStatic.Types (unsafeToPiece)
Expand All @@ -108,6 +110,7 @@ type SwarmAPI =
:<|> "code" :> "run" :> ReqBody '[PlainText] T.Text :> Post '[PlainText] T.Text
:<|> "paths" :> "log" :> Get '[JSON] (RingBuffer CacheLogEntry)
:<|> "repl" :> "history" :> "full" :> Get '[JSON] [REPLHistItem]
:<|> "map" :> Capture "size" AreaDimensions :> Get '[JSON] GridResponse

swarmApi :: Proxy SwarmAPI
swarmApi = Proxy
Expand Down Expand Up @@ -162,6 +165,7 @@ mkApp state events =
:<|> codeRunHandler events
:<|> pathsLogHandler state
:<|> replHandler state
:<|> mapViewHandler state

robotsHandler :: ReadableIORef AppState -> Handler [Robot]
robotsHandler appStateRef = do
Expand Down Expand Up @@ -244,6 +248,18 @@ replHandler appStateRef = do
items = toList replHistorySeq
pure items

mapViewHandler :: ReadableIORef AppState -> AreaDimensions -> Handler GridResponse
mapViewHandler appStateRef areaSize = do
appState <- liftIO (readIORef appStateRef)
let maybeScenario = fst <$> appState ^. uiState . scenarioRef
pure $ case maybeScenario of
Just s ->
GridResponse True
. Just
. getCellGrid s (appState ^. gameState)
$ areaSize
Nothing -> GridResponse False Nothing

-- ------------------------------------------------------------------
-- Main app (used by service and for development)
-- ------------------------------------------------------------------
Expand Down Expand Up @@ -338,3 +354,19 @@ instance ToCapture (Capture "id" RobotID) where
SD.DocCapture
"id" -- name
"(integer) robot ID" -- description

instance FromHttpApiData AreaDimensions where
parseUrlPiece x = left T.pack $ do
pieces <- mapM (readEither . T.unpack) $ T.splitOn "x" x
case pieces of
[w, h] -> return $ AreaDimensions w h
_ -> Left "Need two dimensions"

instance SD.ToSample AreaDimensions where
toSamples _ = SD.samples [AreaDimensions 20 30]

instance ToCapture (Capture "size" AreaDimensions) where
toCapture _ =
SD.DocCapture
"size" -- name
"(integer, integer) dimensions of area" -- description
59 changes: 59 additions & 0 deletions src/Swarm/Web/Worldview.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,59 @@
{-# LANGUAGE OverloadedStrings #-}

-- |
-- SPDX-License-Identifier: BSD-3-Clause
module Swarm.Web.Worldview where

import Control.Lens ((^.))
import Control.Monad.Trans.State
import Data.Aeson (ToJSON)
import Data.Colour.Palette.BrewerSet (Kolor)
import Data.Colour.SRGB (RGB (..), sRGB24, sRGB24show)
import Data.IntMap qualified as IM
import Data.Text qualified as T
import GHC.Generics (Generic)
import Servant.Docs qualified as SD
import Swarm.Game.Entity.Cosmetic (RGBColor, flattenBg)
import Swarm.Game.Scenario (Scenario, scenarioCosmetics)
import Swarm.Game.Scenario.Style
import Swarm.Game.Scenario.Topography.Area (AreaDimensions (..), Grid)
import Swarm.Game.State (GameState, robotInfo)
import Swarm.Game.State.Robot (viewCenter)
import Swarm.Game.Universe (planar)
import Swarm.Game.World.Render
import Swarm.TUI.View.CellDisplay (getTerrainEntityColor)
import Swarm.Util.OccurrenceIndex

data GridResponse = GridResponse
{ isPlaying :: Bool
, grid :: Maybe CellGrid
}
deriving (Generic, ToJSON)

getCellGrid ::
Scenario ->
GameState ->
AreaDimensions ->
CellGrid
getCellGrid myScenario gs requestedSize =
CellGrid indexGrid $ getIndices indexMap
where
vc = gs ^. robotInfo . viewCenter
dg = getDisplayGrid (vc ^. planar) myScenario gs (Just requestedSize)
aMap = myScenario ^. scenarioCosmetics

asColour :: RGBColor -> Kolor
asColour (RGB r g b) = sRGB24 r g b
asHex = HexColor . T.pack . sRGB24show . asColour

f = asHex . maybe (RGB 0 0 0) (flattenBg . fromHiFi) . getTerrainEntityColor aMap
(indexGrid, indexMap) = runState (mapM (encodeOccurrence . f) dg) emptyEncoder

data CellGrid = CellGrid
{ coords :: Grid IM.Key
, colors :: [HexColor]
}
deriving (Generic, ToJSON)

instance SD.ToSample GridResponse where
toSamples _ = SD.noSamples
39 changes: 39 additions & 0 deletions src/swarm-util/Swarm/Util/OccurrenceIndex.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,39 @@
-- |
-- SPDX-License-Identifier: BSD-3-Clause
module Swarm.Util.OccurrenceIndex (
Encoder,
encodeOccurrence,
getIndices,
emptyEncoder,
) where

import Control.Monad.Trans.State
import Data.List (sortOn)
import Data.Map (Map)
import Data.Map qualified as M

type OccurrenceEncoder a = State (Encoder a)

newtype Encoder a = Encoder (Map a Int)

emptyEncoder :: Ord a => Encoder a
emptyEncoder = Encoder mempty

-- | Indices are guaranteed to be contiguous.
getIndices :: Encoder a -> [a]
getIndices (Encoder m) = map fst $ sortOn snd $ M.toList m

-- | Translate each the first occurrence in the structure
-- to a new integer as it is encountered.
-- Subsequent encounters re-use the allocated integer.
encodeOccurrence :: Ord a => a -> OccurrenceEncoder a Int
encodeOccurrence c = do
Encoder currentMap <- get
maybe (cacheNewIndex currentMap) return $
M.lookup c currentMap
where
cacheNewIndex currentMap = do
put $ Encoder $ M.insert c newIdx currentMap
return newIdx
where
newIdx = M.size currentMap
4 changes: 3 additions & 1 deletion swarm.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -103,6 +103,7 @@ library swarm-util
Swarm.Util
Swarm.Util.Erasable
Swarm.Util.Lens
Swarm.Util.OccurrenceIndex
Swarm.Util.Parse
Swarm.Util.RingBuffer
Swarm.Util.UnitInterval
Expand Down Expand Up @@ -288,18 +289,19 @@ library
Swarm.Util.Effect
Swarm.Version
Swarm.Web
Swarm.Web.Worldview

reexported-modules: Control.Carrier.Accum.FixedStrict
, Data.BoolExpr.Simplify
, Swarm.Util
, Swarm.Util.Erasable
, Swarm.Util.Lens
, Swarm.Util.OccurrenceIndex
, Swarm.Util.Parse
, Swarm.Util.RingBuffer
, Swarm.Util.UnitInterval
, Swarm.Util.WindowedCounter
, Swarm.Util.Yaml

other-modules: Paths_swarm
autogen-modules: Paths_swarm

Expand Down
Binary file added web/handwritten-logo.png
Loading
Sorry, something went wrong. Reload?
Sorry, we cannot display this file.
Sorry, this file is invalid so it cannot be displayed.
2 changes: 2 additions & 0 deletions web/index.html
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,9 @@
<title>Swarm server</title>
</head>
<body>
<img src="handwritten-logo.png"/>
<h1>Hello Swarm player!</h1>
<p>Looking for the <a href="api">Web API docs</a>?</p>
<p>Or an <a href="play.html">experimental web frontend</a> for the game?</p>
</body>
</html>
32 changes: 32 additions & 0 deletions web/play.html
Original file line number Diff line number Diff line change
@@ -0,0 +1,32 @@
<!doctype html>
<html>
<head>
<title>Web frontend</title>
<script src="https://pixijs.download/release/pixi.js"></script>

<script src="script/display.js"></script>
<script src="script/fetch.js"></script>

<script>

function startLoop() {
const button = document.getElementById('restart-button');
button.style.display = 'none';

let displayWidth = 600;
let displayHeight = 400;
let out = setupGraphics(button, displayWidth, displayHeight);
let appView = out[0];
let graphics = out[1];
doFetch(button, appView, graphics, displayWidth, displayHeight);
}

window.onload=()=>{
startLoop();
}
</script>
</head>
<body>
<button id="restart-button" onclick="startLoop();" style="display: block;">Restart</button>
</body>
</html>
15 changes: 15 additions & 0 deletions web/script/display.js
Original file line number Diff line number Diff line change
@@ -0,0 +1,15 @@
function setupGraphics(button, displayWidth, displayHeight) {

// Create the application helper and add its render target to the page
let app = new PIXI.Application({
width: displayWidth,
height: displayHeight,
backgroundColor: 0xFFFFFF
});

document.body.insertBefore(app.view, button);

const graphics = new PIXI.Graphics();
app.stage.addChild(graphics);
return [app.view, graphics];
}
Loading

0 comments on commit 253e3a4

Please sign in to comment.