Skip to content

Commit

Permalink
shape recognition with piecewise rows (#2201)
Browse files Browse the repository at this point in the history
# Prerequisites
* #2209
* #2207

# Overview
Certain hacks (e.g. #2115) were employed to better handle "transparency" when recognizing shapes.  However, these approaches are still limited in capability.

The "right" way to use Aho-Corasick with transparency is to break rows up into the contiguous segments separated by transparent cells.  The individual segments recognized by the automaton can then be matched against their expected position.
```
scripts/play.sh --scenario scenarios/Testing/1575-structure-recognizer/2201-piecewise-lines.yaml --autoplay
```
To view the internal shape recognition logs:
```
http://localhost:5357/recognize/log
```

# Other notable changes
* Use `Writer` monad for logging
* Remove all "entity masking" logic
* Update documentation
  • Loading branch information
kostmo authored Nov 17, 2024
1 parent 0ee5d52 commit 27a08ea
Show file tree
Hide file tree
Showing 11 changed files with 686 additions and 362 deletions.
2 changes: 2 additions & 0 deletions data/scenarios/Testing/1575-structure-recognizer/00-ORDER.txt
Original file line number Diff line number Diff line change
Expand Up @@ -16,3 +16,5 @@
1644-rotated-preplacement-recognition.yaml
2115-encroaching-upon-exterior-transparent-cells.yaml
2115-encroaching-upon-interior-transparent-cells.yaml
2201-piecewise-lines.yaml
2201-preclude-overlapping-recognition.yaml
Original file line number Diff line number Diff line change
@@ -0,0 +1,93 @@
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: 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.......
..........
..........
..........
Original file line number Diff line number Diff line change
@@ -0,0 +1,94 @@
version: 1
name: Structure recognition - precluding overlaps
description: |
A cell may be a member of at most one structure.
creative: false
objectives:
- teaser: Recognize one structure
goal:
- |
`line`{=structure} structure should be recognized upon completion.
condition: |
def isRight = \x. case x (\_. false) (\_. true); end;
foundStructure <- structure "line" 0;
return $ isRight foundStructure;
- teaser: Recognize second structure
id: found_elbow
optional: true
goal:
- |
`line`{=structure} structure should be recognized upon completion.
condition: |
def isRight = \x. case x (\_. false) (\_. true); end;
foundStructure <- structure "elbow" 0;
return $ isRight foundStructure;
- teaser: Grab tree
prerequisite:
not: found_elbow
goal:
- |
`grab` the `tree`{=entity} to indicate we are done with the test.
condition: |
as base {has "tree"};
robots:
- name: base
dir: north
devices:
- ADT calculator
- blueprint
- fast grabber
- logger
- treads
inventory:
- [5, rock]
solution: |
place "rock"; move;
place "rock"; move;
place "rock";
turn right;
move;
turn right;
// Try to complete a second structure
place "rock"; move;
place "rock";
// Grab the tree to indicate completion
turn left;
move;
move;
move;
grab;
structures:
- name: elbow
recognize: [north]
structure:
palette:
'x': [stone, rock]
mask: '.'
map: |
xx
.x
- name: line
recognize: [north]
structure:
palette:
'x': [stone, rock]
mask: '.'
map: |
x
x
x
known: [rock]
world:
dsl: |
{blank}
palette:
'.': [grass, erase]
'T': [grass, tree]
'B': [grass, erase, base]
upperleft: [0, 0]
map: |
.......
.....T.
.B.....
7 changes: 6 additions & 1 deletion src/swarm-engine/Swarm/Game/State/Initialize.hs
Original file line number Diff line number Diff line change
Expand Up @@ -42,6 +42,7 @@ import Swarm.Game.Scenario.Topography.Cell (Cell, cellToEntity)
import Swarm.Game.Scenario.Topography.Structure.Recognition
import Swarm.Game.Scenario.Topography.Structure.Recognition.Log
import Swarm.Game.Scenario.Topography.Structure.Recognition.Precompute
import Swarm.Game.Scenario.Topography.Structure.Recognition.Registry (emptyFoundStructures)
import Swarm.Game.Scenario.Topography.Structure.Recognition.Static
import Swarm.Game.Scenario.Topography.Structure.Recognition.Type
import Swarm.Game.State
Expand Down Expand Up @@ -181,7 +182,7 @@ mkRecognizer ::
StaticStructureInfo Cell ->
m (StructureRecognizer (Maybe Cell) Entity)
mkRecognizer structInfo@(StaticStructureInfo structDefs _) = do
foundIntact <- mapM (sequenceA . (id &&& adaptGameState . ensureStructureIntact mtlEntityAt)) allPlaced
foundIntact <- mapM checkIntactness allPlaced

let fs = populateStaticFoundStructures . map fst . filter (null . snd) $ foundIntact
return
Expand All @@ -191,6 +192,10 @@ mkRecognizer structInfo@(StaticStructureInfo structDefs _) = do
fs
[IntactStaticPlacement $ map mkLogEntry foundIntact]
where
-- NOTE: We assume that all static scenario placements are carefully arranged
-- so that overlapping structures are not simultaneously recognized.
checkIntactness = sequenceA . (id &&& adaptGameState . ensureStructureIntact emptyFoundStructures mtlEntityAt)

allPlaced = lookupStaticPlacements cellToEntity structInfo
mkLogEntry (x, intact) =
IntactPlacementLog
Expand Down
Original file line number Diff line number Diff line change
@@ -1,98 +1,72 @@
{-# 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
import Swarm.Game.Location (Location)
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
}
deriving (Generic, ToJSON)

distillLabel :: StructureWithGrid b a -> OrientedStructure
distillLabel swg = OrientedStructure (getName $ originalDefinition swg) (rotatedTo swg)
renderSharedNames :: ConsolidatedRowReferences b a -> Text
renderSharedNames =
T.intercalate "/" . NE.toList . NE.nub . NE.map (getName . originalDefinition . wholeStructure) . referencingRows

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
data ParticipatingEntity e = ParticipatingEntity
{ entity :: e
, searchOffsets :: InspectionOffsets
}
deriving (Functor, Generic, ToJSON)

data FoundRowCandidate e = FoundRowCandidate
{ haystackContext :: HaystackContext e
, soughtContent :: StructureRowContent e
, matchedCandidates :: [MatchingRowFrom]
data IntactPlacementLog e = IntactPlacementLog
{ intactnessFailure :: Maybe (StructureIntactnessFailure e)
, sName :: OriginalName
, locUpperLeft :: Cosmic Location
}
deriving (Functor, Generic, ToJSON)

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

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

data IntactPlacementLog = IntactPlacementLog
{ 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 RowMismatchReason e
= NoKeysSubset (FoundChunkComparison e)
| -- | NOTE: we should never see 'EmptyIntersection',
-- since the earlier 'NoKeysSubset' condition
-- results in an empty intersection
EmptyIntersection
deriving (Functor, Generic, ToJSON)

data SearchLog e
= FoundParticipatingEntity (ParticipatingEntity e)
= IntactStaticPlacement [IntactPlacementLog e]
| 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])
| WorldRowContent [Maybe e]
| ChunksMatchingExpected [ChunkedRowMatch OriginalName e]
| ChunkFailures [ChunkMatchFailureReason e]
| ChunkIntactnessVerification (IntactPlacementLog e)
| 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 27a08ea

Please sign in to comment.