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 0ee5d52 commit f702056
Show file tree
Hide file tree
Showing 9 changed files with 568 additions and 350 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.......
..........
..........
..........
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,54 @@ 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)
renderSharedNames :: ConsolidatedRowReferences b a -> Text
renderSharedNames =
T.intercalate "/" . NE.toList . NE.nub . NE.map (getName . originalDefinition . wholeStructure) . referencingRows

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])
| 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
Original file line number Diff line number Diff line change
Expand Up @@ -17,13 +17,11 @@
--
-- The first searching stage looks for any member row of all participating
-- structure definitions that contains the placed entity.
-- The value returned by the searcher is a second-stage searcher state machine,
-- which this time searches for complete structures of which the found row may
-- be a member.
--
-- Both the first stage and second stage searcher know to start the search
-- at a certain offset horizontally or vertically from the placed entity,
-- based on where within a structure that entity (or row) may occur.
-- If we observe a row in the world that happens to occur in a structure, we use both
-- the horizontal found offset and the index of the row within this structure to compute
-- the expected world location of the candidate structure.
-- Then we perform a full scan of that candidate structure against the world to verify
-- the match.
--
-- Upon locating a complete structure, it is added to a registry
-- (see 'Swarm.Game.Scenario.Topography.Structure.Recognition.Registry.FoundRegistry'), which
Expand Down Expand Up @@ -156,7 +154,7 @@ ensureStructureIntact ::
(Monad s, Hashable a) =>
GenericEntLocator s a ->
FoundStructure b a ->
s (Maybe StructureIntactnessFailure)
s (Maybe (StructureIntactnessFailure a))
ensureStructureIntact entLoader (FoundStructure (StructureWithGrid _ _ (RowWidth w) grid) upperLeft) = do
fmap leftToMaybe . runExceptT . mapM checkLoc $ zip [0 ..] allLocPairs
where
Expand All @@ -166,7 +164,7 @@ ensureStructureIntact entLoader (FoundStructure (StructureWithGrid _ _ (RowWidth
unless (e == Just x)
. except
. Left
. StructureIntactnessFailure idx
. StructureIntactnessFailure x e idx
$ fromIntegral w * length grid

f = fmap ((upperLeft `offsetBy`) . asVector . coordsToLoc) . swap
Expand Down
Loading

0 comments on commit f702056

Please sign in to comment.