License | BSD-3-Clause |
---|---|
Safe Haskell | None |
Language | Haskell2010 |
Swarm.Language.Syntax.Constants
Description
Module provides Types representing built-in functions and commands.
Synopsis
- data Const
- = Noop
- | Wait
- | Selfdestruct
- | Move
- | Backup
- | Volume
- | Path
- | Push
- | Stride
- | Turn
- | Grab
- | Harvest
- | Sow
- | Ignite
- | Place
- | Ping
- | Give
- | Equip
- | Unequip
- | Make
- | Has
- | Equipped
- | Count
- | Drill
- | Use
- | Build
- | Salvage
- | Reprogram
- | Say
- | Listen
- | Log
- | View
- | Appear
- | Create
- | Halt
- | Time
- | Scout
- | Whereami
- | LocateMe
- | Waypoints
- | Structures
- | Floorplan
- | HasTag
- | TagMembers
- | Detect
- | Resonate
- | Density
- | Sniff
- | Chirp
- | Watch
- | Surveil
- | Heading
- | Blocked
- | Scan
- | Upload
- | Ishere
- | Isempty
- | Self
- | Parent
- | Base
- | Meet
- | MeetAll
- | Whoami
- | Setname
- | Random
- | Run
- | If
- | Inl
- | Inr
- | Case
- | Match
- | Force
- | Pure
- | Try
- | Undefined
- | Fail
- | Not
- | Neg
- | Eq
- | Neq
- | Lt
- | Gt
- | Leq
- | Geq
- | Or
- | And
- | Add
- | Sub
- | Mul
- | Div
- | Exp
- | Format
- | Read
- | Erase
- | Concat
- | Chars
- | Split
- | CharAt
- | ToChar
- | AppF
- | Swap
- | Atomic
- | Instant
- | Key
- | InstallKeyHandler
- | Teleport
- | Warp
- | As
- | RobotNamed
- | RobotNumbered
- | Knows
- allConst :: [Const]
- data ConstInfo = ConstInfo {}
- data ConstDoc = ConstDoc {
- effectInfo :: Set CommandEffect
- briefDoc :: Text
- longDoc :: Text
- data ConstMeta
- data MBinAssoc
- data MUnAssoc
- constInfo :: Const -> ConstInfo
- arity :: Const -> Int
- isCmd :: Const -> Bool
- isUserFunc :: Const -> Bool
- isOperator :: Const -> Bool
- isBuiltinFunction :: Const -> Bool
- isTangible :: Const -> Bool
- isLong :: Const -> Bool
- maxSniffRange :: Int32
- maxScoutRange :: Int
- maxStrideRange :: Int
- maxPathRange :: Integer
- globalMaxVolume :: Integer
Documentation
Constants, representing various built-in functions and commands.
IF YOU ADD A NEW CONSTANT, be sure to also update:
1. the constInfo
function (below)
2. the capability checker (Swarm.Language.Capability)
3. the type checker (Swarm.Language.Typecheck)
4. the runtime (Swarm.Game.Step)
5. the emacs mode syntax highlighter (contribs/swarm-mode.el
)
GHC will warn you about incomplete pattern matches for the first
four, and CI will warn you about the last, so in theory it's not
really possible to forget. Note you do not need to update the
parser or pretty-printer, since they are auto-generated from
constInfo
.
Constructors
Noop | Do nothing. This is different than |
Wait | Wait for a number of time steps without doing anything. |
Selfdestruct | Self-destruct. |
Move | Move forward one step. |
Backup | Move backward one step. |
Volume | Measure the size of the enclosed volume |
Path | Describe a path to the destination. |
Push | Push an entity forward one step. |
Stride | Move forward multiple steps. |
Turn | Turn in some direction. |
Grab | Grab an item from the current location. |
Harvest | Harvest an item from the current location. |
Sow | Scatter seeds of a plant |
Ignite | Ignite a combustible item |
Place | Try to place an item at the current location. |
Ping | Obtain the relative location of another robot. |
Give | Give an item to another robot at the current location. |
Equip | Equip a device on oneself. |
Unequip | Unequip an equipped device, returning to inventory. |
Make | Make an item. |
Has | Sense whether we have a certain item. |
Equipped | Sense whether we have a certain device equipped. |
Count | Sense how many of a certain item we have. |
Drill | Drill through an entity. |
Use | Use an entity with another. |
Build | Construct a new robot. |
Salvage | Deconstruct an old robot. |
Reprogram | Reprogram a robot that has executed it's command with a new command |
Say | Emit a message. |
Listen | Listen for a message from other robots. |
Log | Emit a log message. |
View | View a certain robot. |
Appear | Set color and what characters are used for display. |
Create | Create an entity out of thin air. Only available in creative mode. |
Halt | Tell a robot to halt. |
Time | Get current time |
Scout | |
Whereami | Get the current x, y coordinates |
LocateMe | Get the current subworld and x, y coordinates |
Waypoints | Get the list of x, y coordinates of the waypoints for a given name |
Structures | Get the list of x, y coordinates of the southwest corner of all constructed structures of a given name |
Floorplan | Get the width and height of a structure template |
HasTag | Answer whether a given entity has the given tag |
TagMembers | Get the list of entity names that are labeled with a given tag |
Detect | Locate the closest instance of a given entity within the rectangle specified by opposite corners, relative to the current location. |
Resonate | Count the number of a given entity within the rectangle specified by opposite corners, relative to the current location. |
Density | Count the number entities within the rectangle specified by opposite corners, relative to the current location. |
Sniff | Get the distance to the closest instance of the specified entity. |
Chirp | Get the direction to the closest instance of the specified entity. |
Watch | Register a location to interrupt a |
Surveil | Register a (remote) location to interrupt a |
Heading | Get the current heading. |
Blocked | See if we can move forward or not. |
Scan | Scan a nearby cell |
Upload | Upload knowledge to another robot |
Ishere | See if a specific entity is here. |
Isempty | Check whether the current cell is empty |
Self | Get a reference to oneself |
Parent | Get the robot's parent |
Base | Get a reference to the base |
Meet | Meet a nearby robot |
MeetAll | Meet all nearby robots |
Whoami | Get the robot's display name |
Setname | Set the robot's display name |
Random | Get a uniformly random integer. |
Run | Run a program loaded from a file. |
If | If-expressions. |
Inl | Left injection. |
Inr | Right injection. |
Case | Case analysis on a sum type. |
Match | Pair eliminator. |
Force | Force a delayed evaluation. |
Pure | Pure for the cmd monad. |
Try | Try/catch block |
Undefined | Undefined |
Fail | User error |
Not | Logical negation. |
Neg | Arithmetic negation. |
Eq | Logical equality comparison |
Neq | Logical inequality comparison |
Lt | Logical lesser-then comparison |
Gt | Logical greater-then comparison |
Leq | Logical lesser-or-equal comparison |
Geq | Logical greater-or-equal comparison |
Or | Logical or. |
And | Logical and. |
Add | Arithmetic addition operator |
Sub | Arithmetic subtraction operator |
Mul | Arithmetic multiplication operator |
Div | Arithmetic division operator |
Exp | Arithmetic exponentiation operator |
Format | Turn an arbitrary value into a string |
Read | Try to turn a string into a value |
Print a string onto a printable surface | |
Erase | Erase a printable surface |
Concat | Concatenate string values |
Chars | Count number of characters. |
Split | Split string into two parts. |
CharAt | Get the character at an index. |
ToChar | Create a singleton text value with the given character code. |
AppF | Application operator - helps to avoid parentheses:
|
Swap | Swap placed entity with one in inventory. Essentially atomic grab and place. |
Atomic | When executing |
Instant | Like |
Key | Create |
InstallKeyHandler | Install a new keyboard input handler. |
Teleport | Teleport a robot to the given position. |
Warp | Relocate a robot to the given cosmic position. |
As | Run a command as if you were another robot. |
RobotNamed | Find an actor by name. |
RobotNumbered | Find an actor by number. |
Knows | Check if an entity is known. |
Instances
Constructors
ConstInfo | |
Instances
Show ConstInfo Source # | |
Eq ConstInfo Source # | |
Ord ConstInfo Source # | |
Constructors
ConstDoc | |
Fields
|
Constructors
ConstMFunc | Function with arity of which some are commands |
ConstMUnOp MUnAssoc | Unary operator with fixity and associativity. |
ConstMBinOp MBinAssoc | Binary operator with fixity and associativity. |
Instances
Show ConstMeta Source # | |
Eq ConstMeta Source # | |
Ord ConstMeta Source # | |
The meta type representing associativity of binary operator.
Constructors
L | Left associative binary operator (see |
N | Non-associative binary operator (see |
R | Right associative binary operator (see |
Instances
Show MBinAssoc Source # | |
Eq MBinAssoc Source # | |
Ord MBinAssoc Source # | |
The meta type representing associativity of unary operator.
constInfo :: Const -> ConstInfo Source #
Information about constants used in parsing and pretty printing.
It would be more compact to represent the information by testing whether the constants are in certain sets, but using pattern matching gives us warning if we add more constants.
arity :: Const -> Int Source #
The arity of a constant, i.e. how many arguments it expects.
The runtime system will collect arguments to a constant (see
VCApp
) until it has enough, then dispatch
the constant's behavior.
isCmd :: Const -> Bool Source #
Whether a constant represents a command. Constants which are
not commands are functions which are interpreted as soon as
they are evaluated. Commands, on the other hand, are not
interpreted until being executed, that is, when meeting an
FExec
frame. When evaluated, commands simply turn into a
VCApp
.
isUserFunc :: Const -> Bool Source #
Function constants user can call with reserved words (wait
,...).
isOperator :: Const -> Bool Source #
Whether the constant is an operator. Useful predicate for documentation.
isBuiltinFunction :: Const -> Bool Source #
Whether the constant is a function which is interpreted as soon as it is evaluated, but *not* including operators.
Note: This is used for documentation purposes and complements isCmd
and isOperator
in that exactly one will accept a given constant.
isTangible :: Const -> Bool Source #
Whether the constant is a tangible command, that has an external effect on the world. At most one tangible command may be executed per tick.
isLong :: Const -> Bool Source #
Whether the constant is a long command, that is, a tangible
command which could require multiple ticks to execute. Such
commands cannot be allowed in atomic
blocks.
maxScoutRange :: Int Source #
maxStrideRange :: Int Source #
globalMaxVolume :: Integer Source #
Checked upon invocation of the command, before flood fill computation, to ensure the search has a reasonable bound.
The user is warned in the failure message that there exists a global limit.