License | BSD-3-Clause |
---|---|
Safe Haskell | None |
Language | Haskell2010 |
Swarm.Game.Robot
Description
A data type to represent robots.
Synopsis
- _robotID :: RobotR phase -> RobotID phase
- _robotLocation :: RobotR phase -> RobotLocation phase
- type family RobotMachine (phase :: RobotPhase)
- _machine :: RobotR phase -> RobotMachine phase
- type family RobotActivity (phase :: RobotPhase)
- _activityCounts :: RobotR phase -> RobotActivity phase
- type family RobotLogMember (phase :: RobotPhase)
- _robotLog :: RobotR phase -> RobotLogMember phase
- type family RobotLogUpdatedMember (phase :: RobotPhase)
- _robotLogUpdated :: RobotR phase -> RobotLogUpdatedMember phase
- data RobotPhase
- type RID = Int
- data RobotR (phase :: RobotPhase)
- type Robot = RobotR 'ConcreteRobot
- type TRobot = RobotR 'TemplateRobot
- robotEntity :: forall (phase :: RobotPhase) f. Functor f => (Entity -> f Entity) -> RobotR phase -> f (RobotR phase)
- robotName :: Lens' Robot Text
- trobotName :: Lens' TRobot Text
- unwalkableEntities :: Lens' Robot (WalkabilityExceptions EntityName)
- robotCreatedAt :: Lens' Robot TimeSpec
- robotDisplay :: Lens' Robot Display
- robotLocation :: Getter Robot (Cosmic Location)
- unsafeSetRobotLocation :: Cosmic Location -> Robot -> Robot
- trobotLocation :: Lens' TRobot (Maybe (Cosmic Location))
- robotOrientation :: Lens' Robot (Maybe Heading)
- robotInventory :: Lens' Robot Inventory
- trobotInventory :: Lens' TRobot Inventory
- equippedDevices :: Lens' Robot Inventory
- tequippedDevices :: Getter TRobot Inventory
- inventoryHash :: Getter Robot Int
- robotCapabilities :: Getter Robot (MultiEntityCapabilities Entity EntityName)
- walkabilityContext :: Getter Robot WalkabilityContext
- robotID :: Getter Robot RID
- robotParentID :: Lens' Robot (Maybe RID)
- robotHeavy :: Lens' Robot Bool
- systemRobot :: Lens' Robot Bool
- selfDestruct :: Lens' Robot Bool
- runningAtomic :: Lens' Robot Bool
- mkRobot :: Maybe Int -> Text -> Document Syntax -> Maybe (Cosmic Location) -> Heading -> Display -> Maybe TSyntax -> [Entity] -> [(Count, Entity)] -> Bool -> Bool -> WalkabilityExceptions EntityName -> TimeSpec -> TRobot
- robotKnows :: Robot -> Entity -> Bool
- isInteractive :: Robot -> Bool
- hearingDistance :: Num i => i
Robots data
_robotLocation :: RobotR phase -> RobotLocation phase Source #
type family RobotMachine (phase :: RobotPhase) Source #
Instances
type RobotMachine 'TemplateRobot Source # | |
Defined in Swarm.Game.Robot |
_machine :: RobotR phase -> RobotMachine phase Source #
type family RobotActivity (phase :: RobotPhase) Source #
Instances
type RobotActivity 'TemplateRobot Source # | |
Defined in Swarm.Game.Robot |
_activityCounts :: RobotR phase -> RobotActivity phase Source #
type family RobotLogMember (phase :: RobotPhase) Source #
Instances
type RobotLogMember 'TemplateRobot Source # | |
Defined in Swarm.Game.Robot |
_robotLog :: RobotR phase -> RobotLogMember phase Source #
type family RobotLogUpdatedMember (phase :: RobotPhase) Source #
Instances
type RobotLogUpdatedMember 'TemplateRobot Source # | |
Defined in Swarm.Game.Robot |
_robotLogUpdated :: RobotR phase -> RobotLogUpdatedMember phase Source #
Robots
data RobotPhase Source #
The phase of a robot description record.
Constructors
TemplateRobot | The robot record has just been read in from a scenario description; it represents a template that may later be instantiated as one or more concrete robots. |
ConcreteRobot | The robot record represents a concrete robot in the world. |
data RobotR (phase :: RobotPhase) Source #
A value of type RobotR
is a record representing the state of a
single robot. The f
parameter is for tracking whether or not
the robot has been assigned a unique ID.
Instances
FromJSONE TerrainEntityMaps TRobot Source # | We can parse a robot from a YAML file if we have access to an
|
Defined in Swarm.Game.Robot Methods parseJSONE :: Value -> ParserE TerrainEntityMaps TRobot parseJSONE' :: TerrainEntityMaps -> Value -> Parser TRobot | |
Generic (RobotR phase) Source # | |
(Show (RobotLocation phase), Show (RobotID phase), Show (RobotMachine phase), Show (RobotActivity phase), Show (RobotLogMember phase), Show (RobotLogUpdatedMember phase)) => Show (RobotR phase) Source # | |
(Eq (RobotLocation phase), Eq (RobotID phase), Eq (RobotMachine phase), Eq (RobotActivity phase), Eq (RobotLogMember phase), Eq (RobotLogUpdatedMember phase)) => Eq (RobotR phase) Source # | |
FromJSONE (TerrainEntityMaps, RobotMap) Cell | Parse a tuple such as |
Defined in Swarm.Game.Scenario.Topography.Cell Methods parseJSONE :: Value -> ParserE (TerrainEntityMaps, RobotMap) Cell parseJSONE' :: (TerrainEntityMaps, RobotMap) -> Value -> Parser Cell | |
type Rep (RobotR phase) Source # | |
Defined in Swarm.Game.Robot |
type Robot = RobotR 'ConcreteRobot Source #
A concrete robot, with a unique ID number and a specific location.
type TRobot = RobotR 'TemplateRobot Source #
A template robot, i.e. a template robot record without a unique ID number, and possibly without a location.
Lenses
robotEntity :: forall (phase :: RobotPhase) f. Functor f => (Entity -> f Entity) -> RobotR phase -> f (RobotR phase) Source #
Robots are not entities, but they have almost all the
characteristics of one (or perhaps we could think of robots as
very special sorts of entities), so for convenience each robot
carries an Entity
record to store all the information it has in
common with any Entity
.
Note there are various lenses provided for convenience that
directly reference fields inside this record; for example, one
can use robotName
instead of writing
.robotEntity
. entityName
unwalkableEntities :: Lens' Robot (WalkabilityExceptions EntityName) Source #
Entities that the robot cannot move onto
robotDisplay :: Lens' Robot Display Source #
The Display
of a robot. This is a special lens that
automatically sets the curOrientation
to the orientation of the
robot every time you do a get
operation. Technically this does
not satisfy the lens laws---in particular, the get/put law does
not hold. But we should think of the curOrientation
as being
simply a cache of the displayed entity's direction.
robotLocation :: Getter Robot (Cosmic Location) Source #
The robot's current location, represented as (x,y)
. This is only
a getter, since when changing a robot's location we must remember
to update the robotsByLocation
map as well. You can use the
updateRobotLocation
function for this purpose.
unsafeSetRobotLocation :: Cosmic Location -> Robot -> Robot Source #
Set a robot's location. This is unsafe and should never be
called directly except by the updateRobotLocation
function.
The reason is that we need to make sure the robotsByLocation
map stays in sync.
trobotLocation :: Lens' TRobot (Maybe (Cosmic Location)) Source #
A template robot's location. Unlike robotLocation
, this is a
lens, since when dealing with robot templates there is as yet no
robotsByLocation
map to keep up-to-date.
equippedDevices :: Lens' Robot Inventory Source #
A separate inventory for equipped devices, which provide the robot with certain capabilities.
Note that every time the inventory of equipped devices is
modified, this lens recomputes a cached set of the capabilities
the equipped devices provide, to speed up subsequent lookups to
see whether the robot has a certain capability (see robotCapabilities
)
inventoryHash :: Getter Robot Int Source #
A hash of a robot's entity record and equipped devices, to facilitate quickly deciding whether we need to redraw the robot info panel.
robotCapabilities :: Getter Robot (MultiEntityCapabilities Entity EntityName) Source #
Get the set of capabilities this robot possesses. This is only a
getter, not a lens, because it is automatically generated from
the equippedDevices
. The only way to change a robot's
capabilities is to modify its equippedDevices
.
robotID :: Getter Robot RID Source #
The (unique) ID number of the robot. This is only a Getter since the robot ID is immutable.
robotParentID :: Lens' Robot (Maybe RID) Source #
The ID number of the robot's parent, that is, the robot that built (or most recently reprogrammed) this robot, if there is one.
robotHeavy :: Lens' Robot Bool Source #
Is this robot extra heavy (thus requiring tank treads to move)?
systemRobot :: Lens' Robot Bool Source #
Is this robot a "system robot"? System robots are generated by the system (as opposed to created by the user) and are not subject to the usual capability restrictions.
Creation & instantiation
Arguments
:: Maybe Int | |
-> Text | Name of the robot. |
-> Document Syntax | Description of the robot. |
-> Maybe (Cosmic Location) | Initial location. |
-> Heading | Initial heading/direction. |
-> Display | Robot display. |
-> Maybe TSyntax | Initial CESK machine. |
-> [Entity] | Equipped devices. |
-> [(Count, Entity)] | Initial inventory. |
-> Bool | Should this be a system robot? |
-> Bool | Is this robot heavy? |
-> WalkabilityExceptions EntityName | Unwalkable entities |
-> TimeSpec | Creation date |
-> TRobot |
A general function for creating robots.
Query
isInteractive :: Robot -> Bool Source #
Constants
hearingDistance :: Num i => i Source #