Skip to content

Commit

Permalink
scout command
Browse files Browse the repository at this point in the history
  • Loading branch information
kostmo committed Apr 11, 2023
1 parent dc90996 commit 0d5d9ac
Show file tree
Hide file tree
Showing 14 changed files with 192 additions and 20 deletions.
4 changes: 2 additions & 2 deletions data/entities.yaml
Original file line number Diff line number Diff line change
Expand Up @@ -7,7 +7,7 @@
A tall, living entity made of a tough cellular material called "wood".
They regrow after being harvested and are an important raw ingredient used
in making many different devices.
properties: [portable, growable]
properties: [portable, growable, opaque]
growth: [500, 600]

- name: branch
Expand Down Expand Up @@ -117,7 +117,7 @@
char: 'A'
description:
- A mountain. Can be tunneled through with a drill, but it takes time.
properties: [unwalkable]
properties: [unwalkable, opaque]

- name: mountain tunnel
display:
Expand Down
3 changes: 2 additions & 1 deletion data/scenarios/Testing/00-ORDER.txt
Original file line number Diff line number Diff line change
Expand Up @@ -28,4 +28,5 @@
1157-drill-return-value.yaml
1171-sniff-command.yaml
1171-chirp-command.yaml
1171-resonate-command.yaml
1171-resonate-command.yaml
1207-scout-command.yaml
99 changes: 99 additions & 0 deletions data/scenarios/Testing/1207-scout-command.yaml
Original file line number Diff line number Diff line change
@@ -0,0 +1,99 @@
version: 1
name: Scout test
creative: false
description: Locate a robot using scout
objectives:
- goal:
- Grab the flower in front of the exposed bot
condition: |
as base {has "flower"}
solution: |
def search =
found <- scout north;
if found {} {
move;
search;
};
end;
def grabFlower =
here <- ishere "flower";
if here {
grab;
} {
move;
grabFlower;
};
end;
turn east;
search;
turn left;
grabFlower
robots:
- name: base
dir: [0,-1]
display:
char: Ω
attr: robot
devices:
- binoculars
- branch predictor
- compass
- dictionary
- grabber
- logger
- scanner
- string
- treads
- name: bot
dir: [0,1]
system: true
display:
invisible: false
char: b
attr: robot
- name: obscuredbot
dir: [0,1]
system: true
display:
invisible: false
char: o
attr: robot
- name: invisiblebot
dir: [0,1]
system: true
display:
invisible: true
char: i
attr: robot
entities:
- name: binoculars
display:
attr: silver
char: 'B'
description:
- Allows one to "scout" for other robots
properties: [known, portable]
capabilities: [reconline]
known: [tree, flower, boulder]
world:
default: [blank]
palette:
'Ω': [grass, null, base]
'b': [grass, null, bot]
'o': [grass, null, obscuredbot]
'i': [grass, null, invisiblebot]
'.': [grass]
'@': [grass, boulder]
'*': [grass, flower]
'T': [grass, tree]
upperleft: [0, 0]
map: |
.........
..o.i.b..
.........
..T...*..
.........
Ω.......@
.........
1 change: 1 addition & 0 deletions editors/emacs/swarm-mode.el
Original file line number Diff line number Diff line change
Expand Up @@ -75,6 +75,7 @@
"appear"
"create"
"time"
"scout"
"whereami"
"detect"
"resonate"
Expand Down
2 changes: 1 addition & 1 deletion editors/vscode/syntaxes/swarm.tmLanguage.json
Original file line number Diff line number Diff line change
Expand Up @@ -58,7 +58,7 @@
},
{
"name": "keyword.other",
"match": "\\b(?i)(self|parent|base|if|inl|inr|case|fst|snd|force|undefined|fail|not|format|chars|split|charat|tochar|noop|wait|selfdestruct|move|turn|grab|harvest|place|give|equip|unequip|make|has|equipped|count|drill|build|salvage|reprogram|say|listen|log|view|appear|create|time|whereami|detect|resonate|sniff|chirp|heading|blocked|scan|upload|ishere|isempty|meet|meetall|whoami|setname|random|run|return|try|swap|atomic|teleport|as|robotnamed|robotnumbered|knows)\\b"
"match": "\\b(?i)(self|parent|base|if|inl|inr|case|fst|snd|force|undefined|fail|not|format|chars|split|charat|tochar|noop|wait|selfdestruct|move|turn|grab|harvest|place|give|equip|unequip|make|has|equipped|count|drill|build|salvage|reprogram|say|listen|log|view|appear|create|time|scout|whereami|detect|resonate|sniff|chirp|heading|blocked|scan|upload|ishere|isempty|meet|meetall|whoami|setname|random|run|return|try|swap|atomic|teleport|as|robotnamed|robotnumbered|knows)\\b"
}
]
},
Expand Down
2 changes: 2 additions & 0 deletions src/Swarm/Game/Entity.hs
Original file line number Diff line number Diff line change
Expand Up @@ -124,6 +124,8 @@ data EntityProperty
Unwalkable
| -- | Robots can pick this up (via 'Swarm.Language.Syntax.Grab' or 'Swarm.Language.Syntax.Harvest').
Portable
| -- | Obstructs the view of robots that attempt to "scout"
Opaque
| -- | Regrows from a seed after it is harvested.
Growable
| -- | Regenerates infinitely when grabbed or harvested.
Expand Down
13 changes: 13 additions & 0 deletions src/Swarm/Game/Location.hs
Original file line number Diff line number Diff line change
Expand Up @@ -28,6 +28,7 @@ module Swarm.Game.Location (
manhattan,
euclidean,
getElemsInArea,
sigdir,

-- ** reexports for convenience
Affine (..),
Expand Down Expand Up @@ -150,6 +151,18 @@ relativeTo targetDir referenceDir =
enumCount = length (Util.listEnums :: [AbsoluteDir])
indexDiff = ((-) `on` fromEnum) targetDir referenceDir `mod` enumCount

-- | Substitutes all nonzero values with one, preserving sign.
-- Compare to "signorm", which is constrained to class "Floating":
-- https://hackage.haskell.org/package/linear-1.22/docs/Linear-Metric.html#v:signorm
sigdir :: (Ord a, Num a) => V2 a -> V2 a
sigdir = fmap $ signOrdering . compare 0

signOrdering :: Num a => Ordering -> a
signOrdering = \case
LT -> -1
EQ -> 0
GT -> 1

-- | Logic adapted from:
-- https://gamedev.stackexchange.com/questions/49290/#comment213403_49300
nearestDirection :: Heading -> AbsoluteDir
Expand Down
73 changes: 57 additions & 16 deletions src/Swarm/Game/Step.hs
Original file line number Diff line number Diff line change
Expand Up @@ -39,7 +39,7 @@ import Data.Char (chr, ord)
import Data.Either (partitionEithers, rights)
import Data.Either.Extra (eitherToMaybe)
import Data.Foldable (asum, for_, traverse_)
import Data.Foldable.Extra (findM)
import Data.Foldable.Extra (anyM, findM)
import Data.Function (on)
import Data.Functor (void)
import Data.Int (Int32)
Expand Down Expand Up @@ -83,7 +83,7 @@ import Swarm.Language.Pipeline
import Swarm.Language.Pipeline.QQ (tmQ)
import Swarm.Language.Pretty (BulletList (BulletList, bulletListItems), prettyText)
import Swarm.Language.Requirement qualified as R
import Swarm.Language.Syntax
import Swarm.Language.Syntax hiding (P)
import Swarm.Language.Typed (Typed (..))
import Swarm.Language.Value
import Swarm.Util hiding (both)
Expand Down Expand Up @@ -1238,10 +1238,35 @@ execConst c vs s k = do
inv <- use robotInventory
return $ Out (VInt (fromIntegral $ countByName name inv)) s k
_ -> badConst
Scout -> case vs of
[VDir d] -> do
rMap <- use robotMap
myLoc <- use robotLocation
heading <- deriveHeading d

let hasVisibleBot = any f . IS.toList
where
f = maybe False isVisible . (`IM.lookup` rMap)
isVisible = not . (^. robotDisplay . invisible)
isStraightAhead = (== heading) . sigdir . (myLoc .-.)
predicate x =
all
($ x)
[ isStraightAhead . fst
, hasVisibleBot . snd
]

botsByLocs <- use robotsByLocation
hasOrthographicBotLocations <-
anyM (hasSightLineTo myLoc . fst)
. filter predicate
$ M.toList botsByLocs

return $ Out (VBool hasOrthographicBotLocations) s k
_ -> badConst
Whereami -> do
loc <- use robotLocation
let Location x y = loc
return $ Out (VPair (VInt (fromIntegral x)) (VInt (fromIntegral y))) s k
return $ Out (asValue loc) s k
Detect -> case vs of
[VText name, VRect x1 y1 x2 y2] -> do
loc <- use robotLocation
Expand Down Expand Up @@ -1429,16 +1454,14 @@ execConst c vs s k = do
RobotNamed -> case vs of
[VText rname] -> do
r <- robotWithName rname >>= (`isJustOrFail` ["There is no robot named", rname])
let robotValue = VRobot (r ^. robotID)
return $ Out robotValue s k
return $ Out (asValue r) s k
_ -> badConst
RobotNumbered -> case vs of
[VInt rid] -> do
r <-
robotWithID (fromIntegral rid)
>>= (`isJustOrFail` ["There is no robot with number", from (show rid)])
let robotValue = VRobot (r ^. robotID)
return $ Out robotValue s k
return $ Out (asValue r) s k
_ -> badConst
Say -> case vs of
[VText msg] -> do
Expand Down Expand Up @@ -1551,9 +1574,8 @@ execConst c vs s k = do
[VText name] -> do
loc <- use robotLocation
me <- entityAt loc
case me of
Nothing -> return $ Out (VBool False) s k
Just e -> return $ Out (VBool $ isEntityNamed name e) s k
let here = maybe False (isEntityNamed name) me
return $ Out (VBool here) s k
_ -> badConst
Isempty -> do
loc <- use robotLocation
Expand Down Expand Up @@ -1764,7 +1786,7 @@ execConst c vs s k = do

-- Flag the world for a redraw and return the name of the newly constructed robot.
flagRedraw
return $ Out (VRobot (newRobot ^. robotID)) s k
return $ Out (asValue newRobot) s k
_ -> badConst
Salvage -> case vs of
[] -> do
Expand Down Expand Up @@ -1920,11 +1942,25 @@ execConst c vs s k = do
]

rectCells :: Integer -> Integer -> Integer -> Integer -> [V2 Int32]
rectCells x1 y1 x2 y2 = [V2 x y | x <- [fromIntegral xMin .. fromIntegral xMax], y <- [fromIntegral yMin .. fromIntegral yMax]]
rectCells x1 y1 x2 y2 =
rectCellsInt32
(fromIntegral x1)
(fromIntegral y1)
(fromIntegral x2)
(fromIntegral y2)

rectCellsInt32 :: Int32 -> Int32 -> Int32 -> Int32 -> [V2 Int32]
rectCellsInt32 x1 y1 x2 y2 = [V2 x y | x <- [xMin .. xMax], y <- [yMin .. yMax]]
where
(xMin, xMax) = sortPair (x1, x2)
(yMin, yMax) = sortPair (y1, y2)

hasSightLineTo :: HasRobotStepState sig m => Location -> Location -> m Bool
hasSightLineTo (P (V2 x1 y1)) (P (V2 x2 y2)) =
fmap not $ anyM hasOpaque $ rectCellsInt32 x1 y1 x2 y2
where
hasOpaque = fmap (maybe False (`hasProperty` E.Opaque)) . entityAt . P

findNearest ::
HasRobotStepState sig m =>
Text ->
Expand Down Expand Up @@ -1957,12 +1993,17 @@ execConst c vs s k = do
return . (if remTime <= 1 then id else Waiting (remTime + time)) $
Out v s (FImmediate c wf rf : k)

deriveHeading :: HasRobotStepState sig m => Direction -> m Heading
deriveHeading d = do
orient <- use robotOrientation
when (isCardinal d) $ hasCapabilityFor COrient $ TDir d
return $ applyTurn d $ orient ? zero

lookInDirection :: HasRobotStepState sig m => Direction -> m (Location, Maybe Entity)
lookInDirection d = do
newHeading <- deriveHeading d
loc <- use robotLocation
orient <- use robotOrientation
when (isCardinal d) $ hasCapabilityFor COrient (TDir d)
let nextLoc = loc .+^ applyTurn d (orient ? zero)
let nextLoc = loc .+^ newHeading
(nextLoc,) <$> entityAt nextLoc

ensureEquipped :: HasRobotStepState sig m => Text -> m Entity
Expand Down
4 changes: 4 additions & 0 deletions src/Swarm/Game/Value.hs
Original file line number Diff line number Diff line change
Expand Up @@ -12,6 +12,7 @@ import Control.Lens (view)
import Data.Int (Int32)
import Linear (V2 (..))
import Swarm.Game.Entity
import Swarm.Game.Location
import Swarm.Game.Robot
import Swarm.Language.Value

Expand Down Expand Up @@ -43,6 +44,9 @@ instance Valuable Entity where
instance Valuable Robot where
asValue = VRobot . view robotID

instance Valuable Location where
asValue (Location x y) = VPair (VInt (fromIntegral x)) (VInt (fromIntegral y))

instance (Valuable a) => Valuable (Maybe a) where
asValue Nothing = VInj False VUnit
asValue (Just x) = VInj True $ asValue x
Expand Down
3 changes: 3 additions & 0 deletions src/Swarm/Language/Capability.hs
Original file line number Diff line number Diff line change
Expand Up @@ -58,6 +58,8 @@ data Capability
CMake
| -- | Execute the 'Count' command
CCount
| -- | Execute the 'Scout' command. Reconnaissance along a line.
CReconline
| -- | Execute the 'Build' command
CBuild
| -- | Execute the 'Salvage' command
Expand Down Expand Up @@ -220,6 +222,7 @@ constCaps = \case
Atomic -> Just CAtomic
Time -> Just CTime
Wait -> Just CTime
Scout -> Just CReconline
Whereami -> Just CSenseloc
Detect -> Just CDetectloc
Resonate -> Just CDetectcount
Expand Down
5 changes: 5 additions & 0 deletions src/Swarm/Language/Syntax.hs
Original file line number Diff line number Diff line change
Expand Up @@ -246,6 +246,8 @@ data Const

-- | Get current time
Time
| -- Detect whether a robot is within line-of-sight in a direction
Scout
| -- | Get the current x, y coordinates
Whereami
| -- | Locate the closest instance of a given entity within the rectangle
Expand Down Expand Up @@ -607,6 +609,9 @@ constInfo c = case c of
command 1 short . doc "Create an item out of thin air." $
["Only available in creative mode."]
Time -> command 0 Intangible "Get the current time."
Scout ->
command 1 short . doc "Detect whether a robot is within line-of-sight in a direction." $
["Perception is blocked by 'Opaque' entities."]
Whereami -> command 0 Intangible "Get the current x and y coordinates."
Detect ->
command 2 Intangible . doc "Detect an entity within a rectangle." $
Expand Down
1 change: 1 addition & 0 deletions src/Swarm/Language/Typecheck.hs
Original file line number Diff line number Diff line change
Expand Up @@ -561,6 +561,7 @@ inferConst c = case c of
Appear -> [tyQ| text -> cmd unit |]
Create -> [tyQ| text -> cmd unit |]
Time -> [tyQ| cmd int |]
Scout -> [tyQ| dir -> cmd bool |]
Whereami -> [tyQ| cmd (int * int) |]
Detect -> [tyQ| text -> ((int * int) * (int * int)) -> cmd (unit + (int * int)) |]
Resonate -> [tyQ| text -> ((int * int) * (int * int)) -> cmd int |]
Expand Down
1 change: 1 addition & 0 deletions src/Swarm/TUI/View.hs
Original file line number Diff line number Diff line change
Expand Up @@ -947,6 +947,7 @@ displayProperties = displayList . mapMaybe showProperty
showProperty Infinite = Just "infinite"
showProperty Liquid = Just "liquid"
showProperty Unwalkable = Just "blocking"
showProperty Opaque = Just "opaque"
-- Most things are portable so we don't show that.
showProperty Portable = Nothing
-- 'Known' is just a technical detail of how we handle some entities
Expand Down
Loading

0 comments on commit 0d5d9ac

Please sign in to comment.