swarm-0.5.0.0: 2D resource gathering game with programmable robots
LicenseBSD-3-Clause
Safe HaskellSafe-Inferred
LanguageHaskell2010

Swarm.Language.Capability

Description

Capabilities needed to evaluate and execute programs. Language constructs or commands require certain capabilities, and in turn capabilities are provided by various devices. A robot must have an appropriate device equipped in order to make use of each language construct or command.

Synopsis

Documentation

data Capability Source #

Various capabilities which robots can have.

Constructors

CPower

Be powered, i.e. execute anything at all

CMove

Execute the Move command

CBackup

Execute the Backup command

CPath

Execute the Path command

CPush

Execute the Push command

CMovemultiple

Execute the Stride command

CMoveheavy

Execute the Move command for a heavy robot

CTurn

Execute the Turn command

NOTE: using cardinal directions is separate COrient capability

CSelfdestruct

Execute the Selfdestruct command

CGrab

Execute the Grab command

CHarvest

Execute the Harvest command

CIgnite

Execute the Ignite command

CPlace

Execute the Place command

CPing

Execute the Ping command

CGive

Execute the Give command

CEquip

Execute the Equip command

CUnequip

Execute the Unequip command

CMake

Execute the Make command

CCount

Execute the Count command

CRecondir

Execute the Scout command. Reconnaissance along a line in a direction.

CBuild

Execute the Build command

CSalvage

Execute the Salvage command

CDrill

Execute the Drill command

CWaypoint

Execute the Waypoint command

CSenseloc

Execute the Whereami command

CSensefront

Execute the Blocked command

CSensehere

Execute the Ishere and Isempty commands

CDetectloc

Execute the Detect command

CDetectcount

Execute the Resonate and Density commands

CDetectdistance

Execute the Sniff command

CDetectdirection

Execute the Chirp command

CWakeself

Execute the Watch command

CScan

Execute the Scan command

CRandom

Execute the Random command

CAppear

Execute the Appear command

CCreate

Execute the Create command

CListen

Execute the Listen command and passively log messages if also has CLog

CLog

Execute the Log command

CFormat

Format values as text

CConcat

Split text into two pieces

CSplit

Join two text values into one

CCharcount

Count the characters in a text value

CCode

Convert between characters/text and Unicode values

CFloat

Don't drown in liquid

CCond

Evaluate conditional expressions

CNegation

Negate boolean value

CCompare

Evaluate comparison operations

COrient

Use cardinal direction constants.

CArith

Evaluate arithmetic operations

CEnv

Store and look up definitions in an environment

CLambda

Interpret lambda abstractions

CRecursion

Enable recursive definitions

CReprogram

Execute the Reprogram command

CMeet

Execute the meet and meetAll commands.

CWhoami

Capability to introspect and see its own name

CSetname

Capability to set its own name

CTeleport

Capability to move unrestricted to any place

CAtomic

Capability to run commands atomically

CSwap

Capability to execute swap (grab and place atomically at the same time).

CTimeabs

Capability to obtain absolute time, namely via the time command.

CTimerel

Capability to utilize relative passage of time, namely via the wait command. This is strictly weaker than CTimeAbs.

CTry

Capability to execute try.

CSum

Capability for working with sum types.

CProd

Capability for working with product types.

CRecord

Capability for working with record types.

CDebug

Debug capability.

CHandleinput

Capability to handle keyboard input.

CHalt

Capability to make other robots halt.

CGod

God-like capabilities. For e.g. commands intended only for checking challenge mode win conditions, and not for use by players.

Instances

Instances details
FromJSON Capability Source # 
Instance details

Defined in Swarm.Language.Capability

FromJSONKey Capability Source # 
Instance details

Defined in Swarm.Language.Capability

ToJSON Capability Source # 
Instance details

Defined in Swarm.Language.Capability

ToJSONKey Capability Source # 
Instance details

Defined in Swarm.Language.Capability

Data Capability Source # 
Instance details

Defined in Swarm.Language.Capability

Methods

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

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

toConstr :: Capability -> Constr #

dataTypeOf :: Capability -> DataType #

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

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

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

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

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

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

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

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

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

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

Bounded Capability Source # 
Instance details

Defined in Swarm.Language.Capability

Enum Capability Source # 
Instance details

Defined in Swarm.Language.Capability

Generic Capability Source # 
Instance details

Defined in Swarm.Language.Capability

Associated Types

type Rep Capability :: Type -> Type #

Read Capability Source # 
Instance details

Defined in Swarm.Language.Capability

Show Capability Source # 
Instance details

Defined in Swarm.Language.Capability

Eq Capability Source # 
Instance details

Defined in Swarm.Language.Capability

Ord Capability Source # 
Instance details

Defined in Swarm.Language.Capability

Hashable Capability Source # 
Instance details

Defined in Swarm.Language.Capability

PrettyPrec Capability Source # 
Instance details

Defined in Swarm.Language.Pretty

Methods

prettyPrec :: Int -> Capability -> Doc ann Source #

type Rep Capability Source # 
Instance details

Defined in Swarm.Language.Capability

type Rep Capability = D1 ('MetaData "Capability" "Swarm.Language.Capability" "swarm-0.5.0.0-6qXEbhCmuXA4wRndqqhBu" 'False) ((((((C1 ('MetaCons "CPower" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CMove" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "CBackup" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CPath" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "CPush" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CMovemultiple" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "CMoveheavy" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CTurn" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "CSelfdestruct" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CGrab" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "CHarvest" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CIgnite" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "CPlace" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CPing" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "CGive" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "CEquip" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CUnequip" 'PrefixI 'False) (U1 :: Type -> Type)))))) :+: ((((C1 ('MetaCons "CMake" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CCount" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "CRecondir" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CBuild" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "CSalvage" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CDrill" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "CWaypoint" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CSenseloc" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "CSensefront" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CSensehere" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "CDetectloc" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CDetectcount" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "CDetectdistance" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CDetectdirection" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "CWakeself" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "CScan" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CRandom" 'PrefixI 'False) (U1 :: Type -> Type))))))) :+: (((((C1 ('MetaCons "CAppear" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CCreate" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "CListen" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CLog" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "CFormat" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CConcat" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "CSplit" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CCharcount" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "CCode" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CFloat" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "CCond" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CNegation" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "CCompare" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "COrient" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "CArith" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "CEnv" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CLambda" 'PrefixI 'False) (U1 :: Type -> Type)))))) :+: ((((C1 ('MetaCons "CRecursion" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CReprogram" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "CMeet" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CWhoami" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "CSetname" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CTeleport" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "CAtomic" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "CSwap" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CTimeabs" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "CTimerel" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CTry" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "CSum" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CProd" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "CRecord" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CDebug" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "CHandleinput" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "CHalt" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CGod" 'PrefixI 'False) (U1 :: Type -> Type))))))))

constCaps :: Const -> Maybe Capability Source #

Capabilities needed to evaluate or execute a constant.