Skip to content

Commit

Permalink
hack for fixing more integration tests
Browse files Browse the repository at this point in the history
  • Loading branch information
kostmo committed Nov 9, 2024
1 parent 491017c commit 9926535
Show file tree
Hide file tree
Showing 2 changed files with 47 additions and 32 deletions.
Original file line number Diff line number Diff line change
Expand Up @@ -45,10 +45,10 @@ robots:
solution: |
move;
place "silver";
// move; move; move;
// turn left;
// move; move; move; move;
// place "gold";
move; move; move;
turn left;
move; move; move; move;
place "gold";
structures:
- name: chessboard
recognize: [north]
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -22,7 +22,7 @@ import Data.HashMap.Strict qualified as HM
import Data.HashSet qualified as HS
import Data.Hashable (Hashable)
import Data.Int (Int32)
import Data.List (sortOn)
import Data.List (foldl', sortOn)
import Data.List.NonEmpty.Extra qualified as NE
import Data.Map qualified as M
import Data.Maybe (listToMaybe)
Expand Down Expand Up @@ -161,35 +161,53 @@ determineFoundChunksOffset ::
FoundAndExpectedChunkPositions ->
Either ChunkMismatchReason Int
determineFoundChunksOffset (FoundAndExpectedChunkPositions found expected) = do
unless (length found == length expected) $
Left $
WrongNumberOfRecurrences $
WrongRecurrenceCountExplanation
(length found)
found
(length expected)
expected
unless (length found == length expected)
. Left
. WrongNumberOfRecurrences
$ WrongRecurrenceCountExplanation
(length found)
found
(length expected)
expected
unless (allEqual $ NE.toList differences) $
Left $
Misalignment differences
return $ NE.head differences
where
differences = NE.zipWith subtract expected found

data PathAccumulator v = PathAccumulator
{ _currPosition :: HM.HashMap v Int
, acceptedMembers :: [Position v]
, _skippedMembers :: [Position v]
}

-- Compare to the frog/lily pad problem:
-- https://garythomasryan.medium.com/dynamic-programming-for-beginners-a963c1f75674
findNonoverlappingCombinations :: (Hashable v) => [Position v] -> [[Position v]]
findNonoverlappingCombinations xs =
-- FIXME: This is a naive implementation that only takes one path through the DAG
[acceptedMembers result]
where
f (PathAccumulator lastPositions accepted rejects) p@(Position idx len v) =
if idx < HM.findWithDefault 0 v lastPositions
then PathAccumulator lastPositions accepted (p : rejects)
else PathAccumulator (HM.insert v (idx + len) lastPositions) (p : accepted) rejects
result = foldl' f initial xs
initial = PathAccumulator mempty mempty mempty

-- | This runs once per non-overlapping subset of found chunks
checkChunksCombination ::
(Monad m, Hashable a, Eq b) =>
(Cosmic Location -> m (Maybe a)) ->
Cosmic Location ->
RecognitionState b a ->
InspectionOffsets ->
NE.NonEmpty (RowChunkMatchingReference b a) ->
[Position (NE.NonEmpty a)] ->
WriterT [SearchLog a] m (RecognitionState b a)
WriterT [SearchLog a] m [FoundStructure b a]
checkChunksCombination
entLoader
cLoc
rState
horizontalOffsets
pwMaps
candidatesChunked = do
Expand All @@ -206,9 +224,7 @@ checkChunksCombination
map (modifyChunkedRowMatch $ fmap $ getName . originalDefinition . wholeStructure) candidateExpected

let structurePositionsToCheck = map mkFoundStructure candidateExpected
intactStructures <- filterM validateIntactness2d structurePositionsToCheck

registerStructureMatches intactStructures rState
filterM validateIntactness2d structurePositionsToCheck
where
foundRowChunksLookup = binTuplesHM $ map (pVal &&& pIndex) candidatesChunked

Expand Down Expand Up @@ -258,10 +274,7 @@ checkChunksCombination

modifyChunkedRowMatch f (ChunkedRowMatch x y) = ChunkedRowMatch x (f y)

-- | This is the first (one-dimensional) stage
-- in a two-stage (two-dimensional) search.
--
-- It searches for any structure row that happens to
-- | Search for any structure row that happens to
-- contain the placed entity.
registerRowMatches ::
(Monad s, Hashable a, Eq b) =>
Expand All @@ -282,24 +295,26 @@ registerRowMatches entLoader cLoc (AutomatonNewInfo horizontalOffsets _ pwMatche

tell $ pure $ StartSearchAt cLoc horizontalOffsets

let PiecewiseRecognition pwSM pwMaps = pwMatcher

tell . pure . ExpectedChunks $ NE.map (HM.keys . confirmationMap) pwMaps

let candidatesChunked = findAll pwSM entitiesRow
let nonoverlappingChunkCombos = findNonoverlappingCombinations candidatesChunked

-- TODO: Find all combinations of non-overlapping chunks,
-- then run 'checkChunksCombination' for each combination.
intactStructuresLists <- mapM checkCombo nonoverlappingChunkCombos

checkChunksCombination
entLoader
cLoc
rState
horizontalOffsets
pwMaps
candidatesChunked
registerStructureMatches (concat intactStructuresLists) rState
where
registry = rState ^. foundStructures
PiecewiseRecognition pwSM pwMaps = pwMatcher

checkCombo =
checkChunksCombination
entLoader
cLoc
horizontalOffsets
pwMaps

-- |
-- We only allow an entity to participate in one structure at a time,
Expand Down

0 comments on commit 9926535

Please sign in to comment.