swarm-0.7.0.0: 2D resource gathering game with programmable robots
LicenseBSD-3-Clause
Safe HaskellNone
LanguageHaskell2010

Swarm.Language.Syntax.Constants

Description

Module provides Types representing built-in functions and commands.

Synopsis

Documentation

data Const Source #

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 in that it does not take up a time step.

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 wait upon changes

Surveil

Register a (remote) location to interrupt a wait upon changes

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

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: f $ g $ h x = f (g (h x))

Swap

Swap placed entity with one in inventory. Essentially atomic grab and place.

Atomic

When executing atomic c, a robot will not be interrupted, that is, no other robots will execute any commands while the robot is executing c.

Instant

Like atomic, but with no restriction on program size.

Key

Create key values.

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

Instances details
FromJSON Const Source # 
Instance details

Defined in Swarm.Language.Syntax.Constants

FromJSONKey Const Source # 
Instance details

Defined in Swarm.Language.Syntax.Constants

ToJSON Const Source # 
Instance details

Defined in Swarm.Language.Syntax.Constants

ToJSONKey Const Source # 
Instance details

Defined in Swarm.Language.Syntax.Constants

Data Const Source # 
Instance details

Defined in Swarm.Language.Syntax.Constants

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Const -> c Const #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Const #

toConstr :: Const -> Constr #

dataTypeOf :: Const -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Const) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Const) #

gmapT :: (forall b. Data b => b -> b) -> Const -> Const #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Const -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Const -> r #

gmapQ :: (forall d. Data d => d -> u) -> Const -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Const -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Const -> m Const #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Const -> m Const #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Const -> m Const #

Bounded Const Source # 
Instance details

Defined in Swarm.Language.Syntax.Constants

Enum Const Source # 
Instance details

Defined in Swarm.Language.Syntax.Constants

Generic Const Source # 
Instance details

Defined in Swarm.Language.Syntax.Constants

Associated Types

type Rep Const 
Instance details

Defined in Swarm.Language.Syntax.Constants

type Rep Const = D1 ('MetaData "Const" "Swarm.Language.Syntax.Constants" "swarm-0.7.0.0-IuFfgHrMoE7JrptOBRVOwx-swarm-lang" 'False) ((((((C1 ('MetaCons "Noop" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Wait" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Selfdestruct" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Move" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Backup" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Volume" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Path" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "Push" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Stride" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Turn" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Grab" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Harvest" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Sow" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Ignite" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "Place" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Ping" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Give" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Equip" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Unequip" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Make" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Has" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "Equipped" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Count" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Drill" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Use" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Build" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Salvage" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Reprogram" 'PrefixI 'False) (U1 :: Type -> Type)))))) :+: ((((C1 ('MetaCons "Say" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Listen" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Log" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "View" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Appear" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Create" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Halt" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "Time" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Scout" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Whereami" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "LocateMe" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Waypoints" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Structures" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Floorplan" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "HasTag" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "TagMembers" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Detect" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Resonate" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Density" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Sniff" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Chirp" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "Watch" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Surveil" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Heading" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Blocked" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Scan" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Upload" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Ishere" 'PrefixI 'False) (U1 :: Type -> Type))))))) :+: (((((C1 ('MetaCons "Isempty" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Self" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Parent" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Base" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Meet" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "MeetAll" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Whoami" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "Setname" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Random" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Run" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "If" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Inl" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Inr" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Case" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "Match" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Force" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Pure" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Try" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Undefined" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Fail" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Not" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "Neg" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Eq" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Neq" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Lt" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Gt" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Leq" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Geq" 'PrefixI 'False) (U1 :: Type -> Type)))))) :+: ((((C1 ('MetaCons "Or" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "And" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Add" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Sub" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Mul" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Div" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Exp" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "Format" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Read" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Print" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Erase" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Concat" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Chars" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Split" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "CharAt" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ToChar" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AppF" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Swap" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Atomic" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Instant" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Key" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "InstallKeyHandler" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Teleport" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Warp" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "As" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RobotNamed" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "RobotNumbered" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Knows" 'PrefixI 'False) (U1 :: Type -> Type))))))))

Methods

from :: Const -> Rep Const x #

to :: Rep Const x -> Const #

Show Const Source # 
Instance details

Defined in Swarm.Language.Syntax.Constants

Methods

showsPrec :: Int -> Const -> ShowS #

show :: Const -> String #

showList :: [Const] -> ShowS #

Eq Const Source # 
Instance details

Defined in Swarm.Language.Syntax.Constants

Methods

(==) :: Const -> Const -> Bool #

(/=) :: Const -> Const -> Bool #

Ord Const Source # 
Instance details

Defined in Swarm.Language.Syntax.Constants

Methods

compare :: Const -> Const -> Ordering #

(<) :: Const -> Const -> Bool #

(<=) :: Const -> Const -> Bool #

(>) :: Const -> Const -> Bool #

(>=) :: Const -> Const -> Bool #

max :: Const -> Const -> Const #

min :: Const -> Const -> Const #

Hashable Const Source # 
Instance details

Defined in Swarm.Language.Syntax.Constants

Methods

hashWithSalt :: Int -> Const -> Int #

hash :: Const -> Int #

PrettyPrec Const Source # 
Instance details

Defined in Swarm.Language.Syntax.Constants

Methods

prettyPrec :: Int -> Const -> Doc ann

type Rep Const Source # 
Instance details

Defined in Swarm.Language.Syntax.Constants

type Rep Const = D1 ('MetaData "Const" "Swarm.Language.Syntax.Constants" "swarm-0.7.0.0-IuFfgHrMoE7JrptOBRVOwx-swarm-lang" 'False) ((((((C1 ('MetaCons "Noop" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Wait" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Selfdestruct" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Move" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Backup" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Volume" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Path" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "Push" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Stride" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Turn" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Grab" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Harvest" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Sow" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Ignite" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "Place" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Ping" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Give" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Equip" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Unequip" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Make" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Has" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "Equipped" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Count" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Drill" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Use" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Build" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Salvage" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Reprogram" 'PrefixI 'False) (U1 :: Type -> Type)))))) :+: ((((C1 ('MetaCons "Say" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Listen" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Log" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "View" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Appear" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Create" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Halt" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "Time" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Scout" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Whereami" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "LocateMe" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Waypoints" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Structures" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Floorplan" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "HasTag" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "TagMembers" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Detect" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Resonate" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Density" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Sniff" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Chirp" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "Watch" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Surveil" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Heading" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Blocked" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Scan" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Upload" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Ishere" 'PrefixI 'False) (U1 :: Type -> Type))))))) :+: (((((C1 ('MetaCons "Isempty" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Self" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Parent" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Base" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Meet" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "MeetAll" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Whoami" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "Setname" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Random" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Run" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "If" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Inl" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Inr" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Case" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "Match" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Force" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Pure" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Try" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Undefined" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Fail" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Not" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "Neg" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Eq" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Neq" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Lt" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Gt" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Leq" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Geq" 'PrefixI 'False) (U1 :: Type -> Type)))))) :+: ((((C1 ('MetaCons "Or" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "And" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Add" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Sub" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Mul" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Div" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Exp" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "Format" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Read" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Print" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Erase" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Concat" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Chars" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Split" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "CharAt" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ToChar" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AppF" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Swap" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Atomic" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Instant" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Key" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "InstallKeyHandler" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Teleport" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Warp" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "As" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RobotNamed" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "RobotNumbered" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Knows" 'PrefixI 'False) (U1 :: Type -> Type))))))))

data ConstDoc Source #

Constructors

ConstDoc 

Fields

data ConstMeta Source #

Constructors

ConstMFunc

Function with arity of which some are commands

Fields

ConstMUnOp MUnAssoc

Unary operator with fixity and associativity.

ConstMBinOp MBinAssoc

Binary operator with fixity and associativity.

data MBinAssoc Source #

The meta type representing associativity of binary operator.

Constructors

L

Left associative binary operator (see InfixL)

N

Non-associative binary operator (see InfixN)

R

Right associative binary operator (see InfixR)

data MUnAssoc Source #

The meta type representing associativity of unary operator.

Constructors

P

Prefix unary operator (see Prefix)

S

Suffix unary operator (see Suffix)

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.

maxSniffRange :: Int32 Source #

Maximum perception distance for Chirp and Sniff commands

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.