Meeting other robots (#920)

Closes #306. Closes #931.

- Renamed `robot` type to `actor` in anticipation of meeting other things besides robots.
- `meet : cmd (unit + actor)` returns an arbitrary actor within Manhattan distance 1, if any.
- `meetAll : (b -> actor -> cmd b) -> b -> cmd b` will run on every nearby actor.
- Added `antenna` device to provide the commands.
- Added "make a friend" challenge that requires the use of `meet`.
This commit is contained in:
Brent Yorgey 2022-12-22 14:36:11 -06:00 committed by GitHub
parent 56eea8608c
commit 926cede91a
No known key found for this signature in database
GPG Key ID: 4AEE18F83AFDEB23
22 changed files with 388 additions and 57 deletions

View File

@ -106,7 +106,7 @@
char: 'Å'
priority: 11
description:
- A tunnel in a mountain through which robots can freely move.
- A tunnel in a mountain through which anything can freely move.
properties: []
- name: copper ore
@ -710,10 +710,10 @@
place. The item is removed from the robot's inventory and placed
in the robot's current cell (which must be empty). Raises an
exception if the operation fails.
- "The `give` command takes two arguments: the robot to
- "The `give` command takes two arguments: the actor to
give an item to (which can be at most 1 cell away), and the name
of the item to give. Raises an exception if the operation fails."
- "The `install` command takes two arguments: the robot
- "The `install` command takes two arguments: the actor
on which to install a device (which can be at most 1 cell away),
and the name of the device to install."
capabilities: [grab, give, place, install]
@ -966,9 +966,9 @@
attr: device
char: '@'
description:
- "Allows a robot to hear what nearby robots are saying."
- "Allows a robot to hear anything being said nearby."
- "Simply having this device installed will automatically
add messages said by nearby robots to this robot's log,
add messages said by nearby actors to this robot's log,
assuming it has a logger installed."
- "That way you can view any heard message later either in
the logger or the message window."
@ -1076,7 +1076,7 @@
attr: device
char: 'Ю'
description:
- An I/O cable can be used to communicate with an adjacent robot.
- An I/O cable can be used to communicate with adjacent actors.
properties: [portable]
- name: rubber band
@ -1093,7 +1093,7 @@
- "This seems like a safe way to execute `grab` only when there is a
rock to grab. However, it is actually possible for the `grab` to
fail, if some other robot B snatches the rock right after robot A sensed
it and before robot A got around to grab it on the next game tick."
it and before robot A got around to grabbing it on the next game tick."
- "This will make robot A very sad and it will crash."
- "To prevent this situation, robot A can wrap the commands in `atomic`, like so:"
- |
@ -1114,3 +1114,28 @@
- will attempt to move, but if that fails, turn left instead.
properties: [portable]
capabilities: [try]
- name: antenna
display:
attr: silver
char: 'Y'
description:
- A device for transforming electric current into radio waves, and
vice versa.
- |
It can be used to locate nearby actors, by bouncing radio
waves off them and listening for the echo. This capability can be
accessed via two commands:
- |
`meet : cmd (() + actor)` tries to locate a
nearby actor (a robot, or... something else?) up to one cell away.
It returns a reference to the nearest actor, or a unit value if
none are found.
- |
`meetAll : (b -> actor -> cmd b) -> b -> cmd b` runs a command on
every nearby actor (other than oneself), folding over the results
to compute a final result of type `b`. For example, if `x`, `y`,
and `z` are nearby actors, then `meetAll f b0` is equivalent to
`b1 <- f b0 x; b2 <- f b1 y; f b2 z`.
properties: [portable]
capabilities: [meet]

View File

@ -670,6 +670,12 @@
out:
- [1, mirror]
- in:
- [2, silver]
- [2, copper wire]
out:
- [1, antenna]
#########################################
## LAMBDA ##
#########################################

View File

@ -3,5 +3,6 @@ teleport.yaml
2048.yaml
hanoi.yaml
bucket-brigade.yaml
friend.yaml
Mazes
Ranching

View File

@ -0,0 +1,75 @@
def forever : cmd unit -> cmd unit = \c. c ; forever c end
def repeat : int -> cmd unit -> cmd unit =
\n. \c. if (n == 0) {} {c ; repeat (n-1) c}
end
def elif = \t. \then. \else. {if t then else} end
def else = \t. t end
def abs = \n. if (n < 0) {-n} {n} end
def randdir : cmd dir =
d <- random 4;
return (
if (d == 0) {north}
$ elif (d == 1) {east}
$ elif (d == 2) {south}
$ else {west}
)
end
def chooseWait : cmd int =
t <- random (16*2);
return (16 + t)
end
def wander =
d <- randdir;
turn d;
dist <- random 2;
try {repeat dist move} {};
r <- random 5;
if (r == 0) { say "meow" } {}
end
def disappointed = \cat. say "meow??"; cat end
def follow : cmd unit -> actor -> cmd unit = \cat. \r.
rLoc <- as r {whereami};
myLoc <- whereami;
let dx = fst rLoc - fst myLoc in
let dy = snd rLoc - snd myLoc in
if (abs dx > abs dy)
{ if (dx < 0) {turn west} {turn east} }
{ if (dy < 0) {turn south} {turn north} };
if (abs dx != 0 || abs dy != 0) {try { move } { disappointed cat }} {};
wait 4;
follow cat r
end
def love = \cat.
say "purr";
fishGiver <- meet;
case fishGiver
(\_. disappointed cat)
(\r. follow cat r)
end
def cat = \start. \fishCount. \waitTime.
if (waitTime == 0) { wander; start } { wait 1 };
n <- count "fish";
if (n > fishCount)
{ say "yum!";
if (n >= 3) { love start } { cat start n (waitTime - 1) }
}
{ cat start fishCount (waitTime - 1) }
end
def startCat =
n <- count "fish";
w <- chooseWait;
cat startCat n w
end;
startCat

View File

@ -0,0 +1,18 @@
def m2 = move; move end
def m5 = m2; m2; move end
def m10 = m5; m5 end
def m20 = m10; m10 end
def give_fish = \n.
if (n == 0) {}
{ mcat <- meet;
case mcat (\_. give_fish n) (\cat. give cat "fish"; give_fish (n-1))
}
end;
build {
require 3 "fish";
m2; turn left; m20;
give_fish 3;
turn back; m20; turn right; m2
}

View File

@ -0,0 +1,94 @@
version: 1
name: Make a Friend
author: Brent Yorgey
description: |
Win the trust of a furry companion.
creative: false
robots:
- name: base
display:
char: 'Ω'
attr: robot
heavy: true
dir: [0, 1]
devices:
- 3D printer
- ADT calculator
- antenna
- branch predictor
- clock
- comparator
- counter
- dictionary
- grabber
- hearing aid
- lambda
- logger
- mirror
- net
- scanner
- strange loop
- string
- toolkit
- workbench
inventory:
- [10, ADT calculator]
- [10, antenna]
- [10, treads]
- [10, branch predictor]
- [10, fish]
- [10, solar panel]
- [10, grabber]
- [10, lambda]
- [10, strange loop]
- [10, logger]
- [10, clock]
- [10, comparator]
- [10, calculator]
- name: cat
system: true
dir: [-1, 0]
display:
invisible: false
char: 'c'
attr: sand
devices:
- logger
program: |
run "scenarios/Challenges/_friend/cat.sw"
objectives:
- goal:
- There's a cat wandering around in the field. Bring it back to
your base. If you give it something it likes, perhaps you can
get it to follow you.
condition: |
c <- robotNamed "cat";
catLoc <- as c {whereami};
baseLoc <- as base {whereami};
return (catLoc == baseLoc)
solution: |
run "scenarios/Challenges/_friend/friend-solution.sw"
entities:
- name: fish
display:
char: 'f'
description:
- A smelly fish. Rather unappetizing to a robot.
properties: [known, portable]
known: [fish]
seed: 0
world:
offset: true
palette:
'Ω': [grass, null, base]
'.': [stone]
',': [grass]
'c': [grass, null, cat]
'*': [grass, flower]
'@': [stone, boulder]
upperleft: [-20, 2]
map: |-
c,..,,,,,,..,,,,...,.
,..,,,,,,,...........
*,.,@,,,,,,,.....,..Ω

View File

@ -15,3 +15,4 @@
699-movement-fail
858-inventory
710-multi-robot.yaml
920-meet.yaml

View File

@ -0,0 +1,52 @@
version: 1
name: Test meet and meetAll commands
description: |
Make sure meet prefers a robot on the same cell, and test meetAll
by giving everyone a boat.
objectives:
- condition: |
r0 <- robotNamed "other0";
b0 <- as r0 { has "boat" };
teleport self (0,0);
b1 <- meetAll (\b. \r. b0 <- as r {has "boat"}; return (b && b0)) true;
n2 <- as r0 { count "boat" };
return (b0 && b1 && (n2 == 2))
solution: |
mr0 <- meet;
case mr0 (\_. return ()) (\r0. give r0 "boat");
meetAll (\_. \r. give r "boat") ()
robots:
- name: base
loc: [0,0]
dir: [1,0]
devices:
- logger
- antenna
- ADT calculator
- grabber
inventory:
- [7, boat]
- name: other0
loc: [0,0]
dir: [1,0]
- name: other
dir: [1,0]
world:
default: [blank]
palette:
'.': [grass]
'Ω': [grass, null]
'o': [grass, null, other]
'┌': [stone, upper left corner]
'┐': [stone, upper right corner]
'└': [stone, lower left corner]
'┘': [stone, lower right corner]
'─': [stone, horizontal wall]
'│': [stone, vertical wall]
upperleft: [-2, 2]
map: |
┌───┐
│.o.│
│oΩo│
│.o.│
└───┘

View File

@ -15,13 +15,13 @@ def iterate = \state.\com.
end;
// At the beginning all robots can be given Win.
def allOK: robot -> bool = \rob.
def allOK: actor -> bool = \rob.
true
end;
// Try to give a robot a Win, filtering out those that were already given a Win.
// The robot will also receive instructions, so it **must have a logger!**
def tryGive: text -> (robot -> bool) -> int -> cmd (robot -> bool) = \msg.\f.\i.
def tryGive: text -> (actor -> bool) -> int -> cmd (actor -> bool) = \msg.\f.\i.
r <- try {
robotNumbered i;
} {

View File

@ -11,7 +11,7 @@ end;
def while : cmd bool -> {cmd a} -> cmd unit = \test. \body.
ifC test {force body ; while test body} {}
end;
def giveall : robot -> text -> cmd unit = \r. \thing.
def giveall : actor -> text -> cmd unit = \r. \thing.
while (has thing) {give r thing}
end;
def x4 = \c. c; c; c; c end;

View File

@ -81,6 +81,8 @@
"scan"
"upload"
"ishere"
"meet"
"meetall"
"whoami"
"setname"
"random"
@ -104,7 +106,7 @@
"west"
"down"
))
(x-types '("int" "text" "dir" "bool" "cmd" "void" "unit"))
(x-types '("int" "text" "dir" "bool" "cmd" "void" "unit" "actor"))
(x-keywords-regexp (regexp-opt x-keywords 'words))
(x-builtins-regexp (regexp-opt x-builtins 'words))

View File

@ -29,7 +29,7 @@
},
{
"name": "keyword.control.dictionary.let",
"begin": "\\s*let\\s+(\\w+)\\s*(:((\\s*(cmd|dir|text|int|void|unit|\\(|\\)|\\{|\\}|(\\*|\\+|->)|[a-z]\\w*|forall ([a-z]\\w*\\s*)+.)\\s*)+))?=",
"begin": "\\s*let\\s+(\\w+)\\s*(:((\\s*(cmd|dir|text|int|void|unit|actor|\\(|\\)|\\{|\\}|(\\*|\\+|->)|[a-z]\\w*|forall ([a-z]\\w*\\s*)+.)\\s*)+))?=",
"end": "\\s*in",
"beginCaptures": {
"1": {"name": "entity.name.function"},
@ -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|install|equip|unequip|make|has|installed|count|drill|build|salvage|reprogram|say|listen|log|view|appear|create|time|whereami|blocked|scan|upload|ishere|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|install|equip|unequip|make|has|installed|count|drill|build|salvage|reprogram|say|listen|log|view|appear|create|time|whereami|blocked|scan|upload|ishere|meet|meetall|whoami|setname|random|run|return|try|swap|atomic|teleport|as|robotnamed|robotnumbered|knows)\\b"
}
]
},

View File

@ -63,4 +63,4 @@ def clear : cmd unit =
give base "tree";
selfdestruct;
end;
def start : cmd robot = build {turn west; repeat 7 move; clear} end
def start : cmd actor = build {turn west; repeat 7 move; clear} end

View File

@ -163,12 +163,19 @@ data Frame
-- in the given environment (extended by binding the variable,
-- if there is one, to the output of the first command).
FBind (Maybe Var) Term Env
| -- | Discard any environment generated as the result of executing
-- a command.
FDiscardEnv
| -- | Apply specific updates to the world and current robot.
FImmediate WorldUpdate RobotUpdate
| -- | Update the memory cell at a certain location with the computed value.
FUpdate Addr
| -- | Signal that we are done with an atomic computation.
FFinishAtomic
| -- | We are in the middle of running a computation for all the
-- nearby robots. We have the function to run, and the list of
-- robot IDs to run it on.
FMeetAll Value [Int]
deriving (Eq, Show, Generic, FromJSON, ToJSON)
-- | A continuation is just a stack of frames.
@ -350,9 +357,11 @@ prettyFrame (FDef x) = "def " ++ from x ++ " = _"
prettyFrame FExec = "exec _"
prettyFrame (FBind Nothing t _) = "_ ; " ++ prettyString t
prettyFrame (FBind (Just x) t _) = from x ++ " <- _ ; " ++ prettyString t
prettyFrame FDiscardEnv = "discardEnv"
prettyFrame FImmediate {} = "(_ : cmd a)"
prettyFrame (FUpdate loc) = "store@" ++ show loc ++ "(_)"
prettyFrame FFinishAtomic = "finishAtomic"
prettyFrame (FMeetAll _f _rs) = "meetAll"
--------------------------------------------------------------
-- Wrappers for functions in FImmediate

View File

@ -41,7 +41,7 @@ import Data.List qualified as L
import Data.List.NonEmpty (NonEmpty ((:|)))
import Data.List.NonEmpty qualified as NE
import Data.Map qualified as M
import Data.Maybe (catMaybes, fromMaybe, isNothing, listToMaybe)
import Data.Maybe (catMaybes, fromMaybe, isJust, isNothing, listToMaybe)
import Data.Ord (Down (Down))
import Data.Sequence qualified as Seq
import Data.Set (Set)
@ -536,6 +536,15 @@ stepCESK cesk = case cesk of
runningAtomic .= False
return $ Out v s k
-- Machinery for implementing the 'meetAll' command.
-- First case: done meeting everyone.
Out b s (FMeetAll _ [] : k) -> return $ Out b s k
-- More still to meet: apply the function to the current value b and
-- then the next robot id. This will result in a command which we
-- execute, discard any generated environment, and then pass the
-- result to continue meeting the rest of the robots.
Out b s (FMeetAll f (rid : rids) : k) ->
return $ Out b s (FApp f : FArg (TRobot rid) empty : FExec : FDiscardEnv : FMeetAll f rids : k)
-- To execute a bind expression, evaluate and execute the first
-- command, and remember the second for execution later.
Out (VBind mx c1 c2 e) s (FExec : k) -> return $ In c1 e s (FExec : FBind mx c2 e : k)
@ -567,6 +576,9 @@ stepCESK cesk = case cesk of
-- Or, if a command completes with no environment, but there is a
-- previous environment to union with, just use that environment.
Out v s (FUnionEnv e : k) -> return $ Out (VResult v e) s k
-- If there's an explicit DiscardEnv frame, throw away any returned environment.
Out (VResult v _) s (FDiscardEnv : k) -> return $ Out v s k
Out v s (FDiscardEnv : k) -> return $ Out v s k
-- If the top of the continuation stack contains a 'FLoadEnv' frame,
-- it means we are supposed to load up the resulting definition
-- environment, store, and type and capability contexts into the robot's
@ -1077,7 +1089,7 @@ execConst c vs s k = do
As -> case vs of
[VRobot rid, prog] -> do
-- Get the named robot and current game state
r <- robotWithID rid >>= (`isJustOrFail` ["There is no robot with ID", from (show rid)])
r <- robotWithID rid >>= (`isJustOrFail` ["There is no actor with ID", from (show rid)])
g <- get @GameState
-- Execute the given program *hypothetically*: i.e. in a fresh
@ -1163,7 +1175,7 @@ execConst c vs s k = do
[VRobot rid] -> do
_ <-
robotWithID rid
>>= (`isJustOrFail` ["There is no robot with ID", from (show rid), "to view."])
>>= (`isJustOrFail` ["There is no actor with ID", from (show rid), "to view."])
-- Only the base can actually change the view in the UI. Other robots can
-- execute this command but it does nothing (at least for now).
@ -1218,6 +1230,23 @@ execConst c vs s k = do
rid <- use robotID
return $ Out (VRobot (fromMaybe rid mp)) s k
Base -> return $ Out (VRobot 0) s k
Meet -> do
loc <- use robotLocation
rid <- use robotID
g <- get @GameState
let neighbor =
find ((/= rid) . (^. robotID)) -- pick one other than ourself
. sortOn (manhattan loc . (^. robotLocation)) -- prefer closer
$ robotsInArea loc 1 g -- all robots within Manhattan distance 1
return $ Out (VInj (isJust neighbor) (maybe VUnit (VRobot . (^. robotID)) neighbor)) s k
MeetAll -> case vs of
[f, b] -> do
loc <- use robotLocation
rid <- use robotID
g <- get @GameState
let neighborIDs = filter (/= rid) . map (^. robotID) $ robotsInArea loc 1 g
return $ Out b s (FMeetAll f neighborIDs : k)
_ -> badConst
Whoami -> case vs of
[] -> do
name <- use robotName
@ -1292,7 +1321,7 @@ execConst c vs s k = do
-- check if robot exists
childRobot <-
robotWithID childRobotID
>>= (`isJustOrFail` ["There is no robot with ID", from (show childRobotID) <> "."])
>>= (`isJustOrFail` ["There is no actor with ID", from (show childRobotID) <> "."])
-- check that current robot is not trying to reprogram self
myID <- use robotID
@ -1558,6 +1587,8 @@ execConst c vs s k = do
badConstMsg =
T.unlines
[ "Bad application of execConst:"
, T.pack (show c)
, T.pack (show (reverse vs))
, from (prettyCESK (Out (VCApp c (reverse vs)) s k))
]

View File

@ -109,6 +109,8 @@ data Capability
CRecursion
| -- | Execute the 'Reprogram' command
CReprogram
| -- | Execute the `meet` and `meetAll` commands.
CMeet
| -- | Capability to introspect and see its own name
CWhoami
| -- | Capability to set its own name
@ -194,6 +196,8 @@ constCaps = \case
Build -> Just CBuild
Salvage -> Just CSalvage
Reprogram -> Just CReprogram
Meet -> Just CMeet
MeetAll -> Just CMeet
Drill -> Just CDrill
Neg -> Just CArith
Add -> Just CArith

View File

@ -87,7 +87,7 @@ reservedWords =
, "text"
, "dir"
, "bool"
, "robot"
, "actor"
, "cmd"
, "delay"
, "let"
@ -212,7 +212,7 @@ parseTypeAtom =
<|> TyText <$ reserved "text"
<|> TyDir <$ reserved "dir"
<|> TyBool <$ reserved "bool"
<|> TyRobot <$ reserved "robot"
<|> TyActor <$ reserved "actor"
<|> TyCmd <$> (reserved "cmd" *> parseTypeAtom)
<|> TyDelay <$> braces parseType
<|> parens parseType

View File

@ -61,7 +61,7 @@ instance PrettyPrec BaseTy where
prettyPrec _ BDir = "dir"
prettyPrec _ BText = "text"
prettyPrec _ BBool = "bool"
prettyPrec _ BRobot = "robot"
prettyPrec _ BActor = "actor"
instance PrettyPrec IntVar where
prettyPrec _ = pretty . mkVarName "u"
@ -120,7 +120,7 @@ instance PrettyPrec Term where
prettyPrec _ (TText s) = fromString (show s)
prettyPrec _ (TAntiText v) = "$str:" <> pretty v
prettyPrec _ (TBool b) = bool "false" "true" b
prettyPrec _ (TRobot r) = "<r" <> pretty r <> ">"
prettyPrec _ (TRobot r) = "<a" <> pretty r <> ">"
prettyPrec _ (TRef r) = "@" <> pretty r
prettyPrec p (TRequireDevice d) = pparens (p > 10) $ "require" <+> ppr (TText d)
prettyPrec p (TRequire n e) = pparens (p > 10) $ "require" <+> pretty n <+> ppr (TText e)

View File

@ -278,6 +278,10 @@ data Const
Parent
| -- | Get a reference to the base
Base
| -- | Meet a nearby robot
Meet
| -- | Meet all nearby robots
MeetAll
| -- | Get the robot's display name
Whoami
| -- | Set the robot's display name
@ -381,9 +385,9 @@ data Const
Teleport
| -- | Run a command as if you were another robot.
As
| -- | Find a robot by name.
| -- | Find an actor by name.
RobotNamed
| -- | Find a robot by number.
| -- | Find an actor by number.
RobotNumbered
| -- | Check if an entity is known.
Knows
@ -534,7 +538,7 @@ constInfo c = case c of
, "Usually it is automatically inserted where needed, so you do not have to worry about it."
]
Selfdestruct ->
command 0 short . doc "Self-destruct the robot." $
command 0 short . doc "Self-destruct a robot." $
[ "Useful to not clutter the world."
, "This destroys the robot's inventory, so consider `salvage` as an alternative."
]
@ -549,8 +553,8 @@ constInfo c = case c of
Place ->
command 1 short . doc "Place an item at the current location." $
["The current location has to be empty for this to work."]
Give -> command 2 short "Give an item to another robot nearby."
Install -> command 2 short "Install a device from inventory on a robot."
Give -> command 2 short "Give an item to another actor nearby."
Install -> command 2 short "Install a device from inventory on another actor nearby."
Equip -> command 1 short "Equip a device on oneself."
Unequip -> command 1 short "Unequip an equipped device, returning to inventory."
Make -> command 1 long "Make an item using a recipe."
@ -576,7 +580,7 @@ constInfo c = case c of
["Salvaging a robot will give you its inventory, installed devices and log."]
Say ->
command 1 short . doc "Emit a message." $
[ "The message will be in the robots log (if it has one) and the global log."
[ "The message will be in the robot's log (if it has one) and the global log."
, "You can view the message that would be picked by `listen` from the global log "
<> "in the messages panel, along with your own messages and logs."
, "This means that to see messages from other robots you have to be able to listen for them, "
@ -584,14 +588,14 @@ constInfo c = case c of
, "In creative mode, there is of course no such limitation."
]
Listen ->
command 1 long . doc "Listen for a message from other robots." $
[ "It will take the first message said by the closest robot."
command 1 long . doc "Listen for a message from other actors." $
[ "It will take the first message said by the closest actor."
, "You do not need to actively listen for the message to be logged though, "
<> "that is done automatically once you have a listening device installed."
, "Note that you can see the messages either in your logger device or the message panel."
]
Log -> command 1 Intangible "Log the string in the robot's logger."
View -> command 1 short "View the given robot."
View -> command 1 short "View the given actor."
Appear ->
command 1 short . doc "Set how the robot is displayed." $
[ "You can either specify one character or five (for each direction)."
@ -605,7 +609,7 @@ constInfo c = case c of
Blocked -> command 0 Intangible "See if the robot can move forward."
Scan ->
command 0 Intangible . doc "Scan a nearby location for entities." $
[ "Adds the entity (not robot) to your inventory with count 0 if there is any."
[ "Adds the entity (not actor) to your inventory with count 0 if there is any."
, "If you can use sum types, you can also inspect the result directly."
]
Upload -> command 1 short "Upload a robot's known entities and log to another robot."
@ -613,6 +617,8 @@ constInfo c = case c of
Self -> function 0 "Get a reference to the current robot."
Parent -> function 0 "Get a reference to the robot's parent."
Base -> function 0 "Get a reference to the base."
Meet -> command 0 Intangible "Get a reference to a nearby actor, if there is one."
MeetAll -> command 0 long "Run a command for each nearby actor."
Whoami -> command 0 Intangible "Get the robot's display name."
Setname -> command 1 short "Set the robot's display name."
Random ->
@ -682,8 +688,8 @@ constInfo c = case c of
]
Teleport -> command 2 short "Teleport a robot to the given location."
As -> command 2 Intangible "Hypothetically run a command as if you were another robot."
RobotNamed -> command 1 Intangible "Find a robot by name."
RobotNumbered -> command 1 Intangible "Find a robot by number."
RobotNamed -> command 1 Intangible "Find an actor by name."
RobotNumbered -> command 1 Intangible "Find an actor by number."
Knows -> command 1 Intangible "Check if the robot knows about an entity."
where
doc b ls = ConstDoc b (T.unlines ls)
@ -836,7 +842,7 @@ data Term
TAntiText Text
| -- | A Boolean literal.
TBool Bool
| -- | A robot value. These never show up in surface syntax, but are
| -- | A robot reference. These never show up in surface syntax, but are
-- here so we can factor pretty-printing for Values through
-- pretty-printing for Terms.
TRobot Int

View File

@ -336,7 +336,7 @@ infer s@(Syntax l t) = (`catchError` addLocToTypeErr s) $ case t of
TText _ -> return UTyText
TAntiText _ -> return UTyText
TBool _ -> return UTyBool
TRobot _ -> return UTyRobot
TRobot _ -> return UTyActor
-- We should never encounter a TRef since they do not show up in
-- surface syntax, only as values while evaluating (*after*
-- typechecking).
@ -469,33 +469,35 @@ inferConst c = case c of
Grab -> [tyQ| cmd text |]
Harvest -> [tyQ| cmd text |]
Place -> [tyQ| text -> cmd unit |]
Give -> [tyQ| robot -> text -> cmd unit |]
Install -> [tyQ| robot -> text -> cmd unit |]
Give -> [tyQ| actor -> text -> cmd unit |]
Install -> [tyQ| actor -> text -> cmd unit |]
Equip -> [tyQ| text -> cmd unit |]
Unequip -> [tyQ| text -> cmd unit |]
Make -> [tyQ| text -> cmd unit |]
Has -> [tyQ| text -> cmd bool |]
Installed -> [tyQ| text -> cmd bool |]
Count -> [tyQ| text -> cmd int |]
Reprogram -> [tyQ| robot -> {cmd a} -> cmd unit |]
Build -> [tyQ| {cmd a} -> cmd robot |]
Reprogram -> [tyQ| actor -> {cmd a} -> cmd unit |]
Build -> [tyQ| {cmd a} -> cmd actor |]
Drill -> [tyQ| dir -> cmd unit |]
Salvage -> [tyQ| cmd unit |]
Say -> [tyQ| text -> cmd unit |]
Listen -> [tyQ| cmd text |]
Log -> [tyQ| text -> cmd unit |]
View -> [tyQ| robot -> cmd unit |]
View -> [tyQ| actor -> cmd unit |]
Appear -> [tyQ| text -> cmd unit |]
Create -> [tyQ| text -> cmd unit |]
Time -> [tyQ| cmd int |]
Whereami -> [tyQ| cmd (int * int) |]
Blocked -> [tyQ| cmd bool |]
Scan -> [tyQ| dir -> cmd (unit + text) |]
Upload -> [tyQ| robot -> cmd unit |]
Upload -> [tyQ| actor -> cmd unit |]
Ishere -> [tyQ| text -> cmd bool |]
Self -> [tyQ| robot |]
Parent -> [tyQ| robot |]
Base -> [tyQ| robot |]
Self -> [tyQ| actor |]
Parent -> [tyQ| actor |]
Base -> [tyQ| actor |]
Meet -> [tyQ| cmd (unit + actor) |]
MeetAll -> [tyQ| (b -> actor -> cmd b) -> b -> cmd b |]
Whoami -> [tyQ| cmd text |]
Setname -> [tyQ| text -> cmd unit |]
Random -> [tyQ| int -> cmd int |]
@ -535,10 +537,10 @@ inferConst c = case c of
AppF -> [tyQ| (a -> b) -> a -> b |]
Swap -> [tyQ| text -> cmd text |]
Atomic -> [tyQ| cmd a -> cmd a |]
Teleport -> [tyQ| robot -> (int * int) -> cmd unit |]
As -> [tyQ| robot -> {cmd a} -> cmd a |]
RobotNamed -> [tyQ| text -> cmd robot |]
RobotNumbered -> [tyQ| int -> cmd robot |]
Teleport -> [tyQ| actor -> (int * int) -> cmd unit |]
As -> [tyQ| actor -> {cmd a} -> cmd a |]
RobotNamed -> [tyQ| text -> cmd actor |]
RobotNumbered -> [tyQ| int -> cmd actor |]
Knows -> [tyQ| text -> cmd bool |]
where
cmpBinT = [tyQ| a -> a -> bool |]

View File

@ -29,7 +29,7 @@ module Swarm.Language.Types (
pattern TyText,
pattern TyDir,
pattern TyBool,
pattern TyRobot,
pattern TyActor,
pattern (:+:),
pattern (:*:),
pattern (:->:),
@ -46,7 +46,7 @@ module Swarm.Language.Types (
pattern UTyText,
pattern UTyDir,
pattern UTyBool,
pattern UTyRobot,
pattern UTyActor,
pattern UTySum,
pattern UTyProd,
pattern UTyFun,
@ -111,8 +111,11 @@ data BaseTy
BDir
| -- | Booleans.
BBool
| -- | Robots.
BRobot
| -- | "Actors", i.e. anything that can do stuff. Internally, these
-- are all just "robots", but we give them a more generic
-- in-game name because they could represent other things like
-- aliens, animals, seeds, ...
BActor
deriving (Eq, Ord, Show, Data, Generic, FromJSON, ToJSON)
-- | A "structure functor" encoding the shape of type expressions.
@ -312,8 +315,8 @@ pattern TyDir = Fix (TyBaseF BDir)
pattern TyBool :: Type
pattern TyBool = Fix (TyBaseF BBool)
pattern TyRobot :: Type
pattern TyRobot = Fix (TyBaseF BRobot)
pattern TyActor :: Type
pattern TyActor = Fix (TyBaseF BActor)
infixr 5 :+:
@ -360,8 +363,8 @@ pattern UTyDir = UTerm (TyBaseF BDir)
pattern UTyBool :: UType
pattern UTyBool = UTerm (TyBaseF BBool)
pattern UTyRobot :: UType
pattern UTyRobot = UTerm (TyBaseF BRobot)
pattern UTyActor :: UType
pattern UTyActor = UTerm (TyBaseF BActor)
pattern UTySum :: UType -> UType -> UType
pattern UTySum ty1 ty2 = UTerm (TySumF ty1 ty2)

View File

@ -159,6 +159,7 @@ testScenarioSolution _ci _em =
, testSolution Default "Challenges/teleport"
, testSolution (Sec 5) "Challenges/2048"
, testSolution (Sec 10) "Challenges/hanoi"
, testSolution Default "Challenges/friend"
, testGroup
"Mazes"
[ testSolution Default "Challenges/Mazes/easy_cave_maze"
@ -216,6 +217,7 @@ testScenarioSolution _ci _em =
, testSolution Default "Testing/699-movement-fail/699-move-liquid"
, testSolution Default "Testing/699-movement-fail/699-teleport-blocked"
, testSolution Default "Testing/710-multi-robot"
, testSolution Default "Testing/920-meet"
]
]
where