Skip to content

Commit

Permalink
Structure recognition with discontiguous row chunks
Browse files Browse the repository at this point in the history
  • Loading branch information
kostmo committed Nov 14, 2024
1 parent ca229ee commit cf4208f
Show file tree
Hide file tree
Showing 14 changed files with 633 additions and 387 deletions.
Original file line number Diff line number Diff line change
Expand Up @@ -16,3 +16,4 @@
1644-rotated-preplacement-recognition.yaml
2115-encroaching-upon-exterior-transparent-cells.yaml
2115-encroaching-upon-interior-transparent-cells.yaml
2201-piecewise-lines.yaml
Original file line number Diff line number Diff line change
@@ -0,0 +1,110 @@
version: 1
name: Structure recognition - piecewise row recognition
description: |
Demonstrate general solution for transparency.
In this scenario, a structure called `spaceship`{=structure} is occluded
by a single cell overlay shape called `damage`{=structure}.
The base swaps the "damage" entity with the correct part.
creative: false
objectives:
- teaser: Recognize structure
goal:
- |
`spaceship`{=structure} structure should be recognized upon completion.
condition: |
def isRight = \x. case x (\_. false) (\_. true); end;
foundStructure <- structure "spaceship" 0;
return $ isRight foundStructure;
robots:
- name: base
dir: east
devices:
- ADT calculator
- blueprint
- fast grabber
- logger
- treads
inventory:
- [1, rock]
solution: |
move; move; move; move; move; move; move;
swap "rock";
structures:
- name: fragment
recognize: [north]
structure:
palette:
'z': [stone, pixel (R)]
'w': [stone, pixel (B)]
'x': [stone, rock]
'y': [stone, mountain]
mask: '.'
map: |
zw.xy
- name: spaceship
recognize: [north]
structure:
palette:
'p': [stone, board]
'x': [stone, rock]
'y': [stone, mountain]
'z': [stone, pixel (R)]
'w': [stone, pixel (B)]
'q': [stone, pixel (G)]
mask: '.'
map: |
q....xy.zw.xy
qq....ppp....
q....xy.xy.qq
- name: friendship
recognize: [north]
structure:
palette:
'x': [stone, rock]
'y': [stone, mountain]
'z': [stone, pixel (R)]
'w': [stone, pixel (B)]
'q': [stone, pixel (G)]
mask: '.'
map: |
qqq.......
qqq.......
qqq.......
qqq.......
..xy.zw.xy
qqq.......
- name: damage
description: A single-cell overwrite of the spaceship
structure:
palette:
't': [stone, tree]
map: |
t
- name: modified ship
description: A spaceship with a single cell replaced by a `tree`{=entity}
structure:
placements:
- src: spaceship
- src: damage
offset: [5, 0]
map: ""
known: [board, mountain, rock, tree, pixel (R), pixel (B)]
world:
dsl: |
{blank}
palette:
'.': [grass, erase]
'B': [grass, erase, base]
'p':
structure:
name: modified ship
cell: [grass]
upperleft: [100, -100]
map: |
..........
B.p.......
..........
..........
..........
4 changes: 0 additions & 4 deletions data/schema/placement.json
Original file line number Diff line number Diff line change
Expand Up @@ -10,10 +10,6 @@
"type": "string",
"description": "Name of structure definition"
},
"truncate": {
"type": "boolean",
"description": "Overlay should be truncated if it exceeds bounds of target structure"
},
"offset": {
"$ref": "planar-loc.json"
},
Expand Down
2 changes: 1 addition & 1 deletion data/schema/structure.json
Original file line number Diff line number Diff line change
Expand Up @@ -26,7 +26,7 @@
}
},
"placements": {
"description": "Structure placements. Earlier members may occlude later members of the list.",
"description": "Structure placements. Later members may occlude earlier members of the list.",
"type": "array",
"items": {
"$ref": "placement.json"
Expand Down
2 changes: 1 addition & 1 deletion data/schema/world.json
Original file line number Diff line number Diff line change
Expand Up @@ -28,7 +28,7 @@
}
},
"placements": {
"description": "Structure placements. Earlier members may occlude later members of the list.",
"description": "Structure placements. Later members may occlude earlier members of the list.",
"type": "array",
"items": {
"$ref": "placement.json"
Expand Down
27 changes: 4 additions & 23 deletions src/swarm-engine/Swarm/Game/State/Initialize.hs
Original file line number Diff line number Diff line change
Expand Up @@ -15,7 +15,6 @@ import Control.Effect.Lens (view)
import Control.Effect.Lift (Has)
import Control.Effect.State (State)
import Control.Lens hiding (Const, use, uses, view, (%=), (+=), (.=), (<+=), (<<.=))
import Data.Foldable.Extra (allM)
import Data.IntMap qualified as IM
import Data.List (partition)
import Data.List.NonEmpty (NonEmpty)
Expand All @@ -25,7 +24,6 @@ import Data.Map qualified as M
import Data.Maybe (isNothing)
import Data.Set qualified as S
import Data.Text (Text)
import Linear (V2 (..))
import Swarm.Game.CESK (finalValue, initMachine)
import Swarm.Game.Device (getCapabilitySet, getMap)
import Swarm.Game.Entity
Expand All @@ -50,7 +48,7 @@ import Swarm.Game.State
import Swarm.Game.State.Landscape (mkLandscape)
import Swarm.Game.State.Robot (setRobotInfo)
import Swarm.Game.State.Substate
import Swarm.Game.Universe as U (offsetBy)
import Swarm.Game.Step.Util (adaptGameState)
import Swarm.Game.World.Gen (Seed)
import Swarm.Language.Capability (constCaps)
import Swarm.Language.Syntax (allConst, erase)
Expand Down Expand Up @@ -183,8 +181,9 @@ mkRecognizer ::
StaticStructureInfo Cell ->
m (StructureRecognizer (Maybe Cell) Entity)
mkRecognizer structInfo@(StaticStructureInfo structDefs _) = do
foundIntact <- mapM (sequenceA . (id &&& ensureStructureIntact)) allPlaced
let fs = populateStaticFoundStructures . map fst . filter snd $ foundIntact
foundIntact <- mapM (sequenceA . (id &&& adaptGameState . ensureStructureIntact mtlEntityAt)) allPlaced

let fs = populateStaticFoundStructures . map fst . filter (null . snd) $ foundIntact
return
$ StructureRecognizer
(mkAutomatons cellToEntity structDefs)
Expand All @@ -199,24 +198,6 @@ mkRecognizer structInfo@(StaticStructureInfo structDefs _) = do
((getName . originalDefinition . structureWithGrid) x)
(upperLeftCorner x)

-- | Matches definitions against the placements.
-- Fails fast (short-circuits) if a non-matching
-- cell is encountered.
ensureStructureIntact ::
(Has (State GameState) sig m) =>
FoundStructure (Maybe Cell) Entity ->
m Bool
ensureStructureIntact (FoundStructure (StructureWithGrid _ _ grid) upperLeft) =
allM outer $ zip [0 ..] grid
where
outer (y, row) = allM (inner y) $ zip [0 ..] row
inner y (x, maybeTemplateEntity) = case maybeTemplateEntity of
Nothing -> return True
Just _ ->
fmap (== maybeTemplateEntity) $
entityAt $
upperLeft `offsetBy` V2 x (negate y)

buildTagMap :: EntityMap -> Map Text (NonEmpty EntityName)
buildTagMap em =
binTuples expanded
Expand Down
18 changes: 11 additions & 7 deletions src/swarm-engine/Swarm/Game/Step/Util.hs
Original file line number Diff line number Diff line change
Expand Up @@ -62,6 +62,15 @@ lookInDirection d = do
let nextLoc = loc `offsetBy` newHeading
(nextLoc,) <$> entityAt nextLoc

adaptGameState ::
Has (State GameState) sig m =>
TS.State GameState b ->
m b
adaptGameState f = do
(newRecognizer, newGS) <- TS.runState f <$> get
put newGS
return newRecognizer

-- | Modify the entity (if any) at a given location.
updateEntityAt ::
(Has (State Robot) sig m, Has (State GameState) sig m) =>
Expand All @@ -77,14 +86,9 @@ updateEntityAt cLoc@(Cosmic subworldName loc) upd = do
currentTick <- use $ temporal . ticks
myID <- use robotID
zoomRobots $ wakeWatchingRobots myID currentTick cLoc
oldRecognizer <- use $ discovery . structureRecognition

oldGS <- get @GameState
let (newRecognizer, newGS) =
flip TS.runState oldGS $
SRT.entityModified mtlEntityAt modType cLoc oldRecognizer
put newGS

oldRecognizer <- use $ discovery . structureRecognition
newRecognizer <- adaptGameState $ SRT.entityModified mtlEntityAt modType cLoc oldRecognizer
discovery . structureRecognition .= newRecognizer

pcr <- use $ pathCaching . pathCachingRobots
Expand Down
Original file line number Diff line number Diff line change
@@ -1,12 +1,16 @@
{-# LANGUAGE OverloadedStrings #-}

-- |
-- SPDX-License-Identifier: BSD-3-Clause
--
-- Types strictly for debugging structure recognition via the web interface
module Swarm.Game.Scenario.Topography.Structure.Recognition.Log where

import Data.Aeson
import Data.Int (Int32)
import Data.List.NonEmpty (NonEmpty)
import Data.List.NonEmpty qualified as NE
import Data.Text (Text)
import Data.Text qualified as T
import GHC.Generics (Generic)
import Servant.Docs (ToSample)
import Servant.Docs qualified as SD
Expand All @@ -15,11 +19,6 @@ import Swarm.Game.Scenario.Topography.Structure.Recognition.Type
import Swarm.Game.Universe (Cosmic)
import Swarm.Language.Syntax.Direction (AbsoluteDir)

-- | Type aliases for documentation
type StructureRowContent e = SymbolSequence e

type WorldRowContent e = SymbolSequence e

data OrientedStructure = OrientedStructure
{ oName :: OriginalName
, oDir :: AbsoluteDir
Expand All @@ -29,70 +28,57 @@ data OrientedStructure = OrientedStructure
distillLabel :: StructureWithGrid b a -> OrientedStructure
distillLabel swg = OrientedStructure (getName $ originalDefinition swg) (rotatedTo swg)

data MatchingRowFrom = MatchingRowFrom
{ topDownRowIdx :: Int32
-- ^ numbered from the top down
, structure :: OrientedStructure
}
deriving (Generic, ToJSON)

newtype HaystackPosition = HaystackPosition Int
deriving (Generic, ToJSON)

data HaystackContext e = HaystackContext
{ maskedWorldRow :: WorldRowContent e
-- ^ entities that do not constitute any of the eligible structures
-- are replaced with 'null' in this list.
, haystackPosition :: HaystackPosition
}
deriving (Functor, Generic, ToJSON)
renderSharedNames :: ConsolidatedRowReferences b a -> Text
renderSharedNames =
T.intercalate "/" . NE.toList . NE.nub . NE.map (getName . originalDefinition . wholeStructure) . referencingRows

data FoundRowCandidate e = FoundRowCandidate
{ haystackContext :: HaystackContext e
, soughtContent :: StructureRowContent e
, matchedCandidates :: [MatchingRowFrom]
}
deriving (Functor, Generic, ToJSON)

data EntityKeyedFinder e = EntityKeyedFinder
newtype EntityKeyedFinder = EntityKeyedFinder
{ searchOffsets :: InspectionOffsets
, candidateStructureRows :: NonEmpty (StructureRowContent e)
, entityMask :: [e]
-- ^ NOTE: HashSet has no Functor instance,
-- so we represent this as a list here.
}
deriving (Functor, Generic, ToJSON)
deriving (Generic, ToJSON)

data ParticipatingEntity e = ParticipatingEntity
{ entity :: e
, entityKeyedFinders :: NonEmpty (EntityKeyedFinder e)
, entityKeyedFinders :: EntityKeyedFinder
}
deriving (Functor, Generic, ToJSON)

data IntactPlacementLog = IntactPlacementLog
{ isIntact :: Bool
{ intactnessFailure :: Maybe StructureIntactnessFailure
, sName :: OriginalName
, locUpperLeft :: Cosmic Location
}
deriving (Generic, ToJSON)

data VerticalSearch e = VerticalSearch
{ haystackVerticalExtents :: InspectionOffsets
-- ^ vertical offset of haystack relative to the found row
, soughtStructures :: [OrientedStructure]
, verticalHaystack :: [WorldRowContent e]
data ChunkMatchFailureReason e
= ChunkMatchFailureReason OriginalName (RowMismatchReason e)
deriving (Functor, Generic, ToJSON)

data FoundChunkComparison e = FoundChunkComparison
{ foundChunkKeys :: [NonEmpty e]
, referenceChunkKeys :: [NonEmpty e]
}
deriving (Functor, Generic, ToJSON)

data RowMismatchReason e
= NoKeysSubset (FoundChunkComparison e)
| -- | NOTE: should be redundant with 'NoKeysSubset'
EmptyIntersection
deriving (Functor, Generic, ToJSON)

data SearchLog e
= FoundParticipatingEntity (ParticipatingEntity e)
= IntactStaticPlacement [IntactPlacementLog]
| StartSearchAt (Cosmic Location) InspectionOffsets
| FoundParticipatingEntity (ParticipatingEntity e)
| FoundCompleteStructureCandidates [(OrientedStructure, Cosmic Location)]
| -- | this is actually internally used as a (Map (NonEmpty e) (NonEmpty Int)),
-- but the requirements of Functor force us to invert the mapping
FoundPiecewiseChunks [(NonEmpty Int, NonEmpty e)]
| ExpectedChunks (NonEmpty [NonEmpty e])
| ChunksMatchingExpected [ChunkedRowMatch OriginalName e]
| ChunkFailures [ChunkMatchFailureReason e]
| ChunkIntactnessVerification IntactPlacementLog
| StructureRemoved OriginalName
| FoundRowCandidates [FoundRowCandidate e]
| FoundCompleteStructureCandidates [OrientedStructure]
| -- | There may be multiple candidate structures that could be
-- completed by the element that was just placed. This lists all of them.
VerticalSearchSpans [VerticalSearch e]
| IntactStaticPlacement [IntactPlacementLog]
deriving (Functor, Generic)

instance (ToJSON e) => ToJSON (SearchLog e) where
Expand Down
Loading

0 comments on commit cf4208f

Please sign in to comment.