License | BSD-3-Clause |
---|---|
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
An Entity
represents an object that exists in the world. Each
entity has a way to be displayed, some metadata such as a name and
description, some properties, and possibly an inventory of other
entities.
This module also defines the Inventory
type, since the two types
are mutually recursive (an inventory contains entities, which can
have inventories).
Synopsis
- type EntityName = Text
- data EntityProperty
- = Unwalkable
- | Pickable
- | Pushable
- | Opaque
- | Growable
- | Combustible
- | Infinite
- | Liquid
- | Known
- newtype GrowthTime = GrowthTime (Integer, Integer)
- data GrowthSpread = GrowthSpread {}
- data Growth = Growth {}
- defaultGrowth :: Growth
- data Combustibility = Combustibility {}
- defaultCombustibility :: Combustibility
- data Entity
- mkEntity :: Display -> Text -> Document Syntax -> [EntityProperty] -> Set Capability -> Entity
- entityDisplay :: Lens' Entity Display
- entityName :: Lens' Entity EntityName
- entityPlural :: Lens' Entity (Maybe Text)
- entityNameFor :: Int -> Getter Entity Text
- entityDescription :: Lens' Entity (Document Syntax)
- entityTags :: Lens' Entity (Set Text)
- entityOrientation :: Lens' Entity (Maybe Heading)
- entityGrowth :: Lens' Entity (Maybe Growth)
- entityCombustion :: Lens' Entity (Maybe Combustibility)
- entityYields :: Lens' Entity (Maybe Text)
- entityProperties :: Lens' Entity (Set EntityProperty)
- hasProperty :: Entity -> EntityProperty -> Bool
- entityCapabilities :: Lens' Entity (SingleEntityCapabilities EntityName)
- entityBiomes :: Lens' Entity (Set TerrainType)
- entityInventory :: Lens' Entity Inventory
- entityHash :: Getter Entity Int
- data EntityMap = EntityMap {}
- buildEntityMap :: Has (Throw LoadingFailure) sig m => [Entity] -> m EntityMap
- lookupEntityE :: Map Text b -> Text -> Either Text b
- validateEntityAttrRefs :: Has (Throw LoadingFailure) sig m => Set WorldAttr -> [Entity] -> m ()
- loadEntities :: (Has (Throw SystemFailure) sig m, Has (Lift IO) sig m) => m EntityMap
- allEntities :: EntityMap -> [Entity]
- lookupEntityName :: Text -> EntityMap -> Maybe Entity
- devicesForCap :: Capability -> EntityMap -> [Entity]
- data Inventory
- empty :: Inventory
- singleton :: Entity -> Inventory
- fromList :: [Entity] -> Inventory
- fromElems :: [(Count, Entity)] -> Inventory
- lookup :: Entity -> Inventory -> Count
- lookupByName :: Text -> Inventory -> [Entity]
- countByName :: Text -> Inventory -> Count
- contains :: Inventory -> Entity -> Bool
- contains0plus :: Entity -> Inventory -> Bool
- elems :: Inventory -> [(Count, Entity)]
- isSubsetOf :: Inventory -> Inventory -> Bool
- isEmpty :: Inventory -> Bool
- inventoryCapabilities :: Inventory -> MultiEntityCapabilities Entity EntityName
- extantElemsWithCapability :: Capability -> Inventory -> [Entity]
- entitiesByCapability :: Inventory -> Map Capability (NonEmpty Entity)
- insert :: Entity -> Inventory -> Inventory
- insertCount :: Count -> Entity -> Inventory -> Inventory
- delete :: Entity -> Inventory -> Inventory
- deleteCount :: Count -> Entity -> Inventory -> Inventory
- deleteAll :: Entity -> Inventory -> Inventory
- union :: Inventory -> Inventory -> Inventory
- difference :: Inventory -> Inventory -> Inventory
Entity properties
type EntityName = Text Source #
A type representing entity names, currently a synonym for Text
.
In the future it is conceivable that it might become more complex.
data EntityProperty Source #
Various properties that an entity can have, which affect how robots can interact with it.
Unwalkable | Robots can't move onto a cell containing this entity. |
Pickable | |
Pushable | Robots can |
Opaque | Obstructs the view of robots that attempt to "scout" |
Growable | Regrows from a seed after it is harvested. |
Combustible | Can burn when ignited (either via |
Infinite | Regenerates infinitely when grabbed or harvested. |
Liquid | Robots drown if they walk on this without a boat. |
Known | Robots automatically know what this is without having to scan it. |
Instances
newtype GrowthTime Source #
How long an entity takes to regrow. This represents the minimum and maximum amount of time taken by one growth stage (there are two stages). The actual time for each stage will be chosen uniformly at random between these two values.
Instances
data GrowthSpread Source #
GrowthSpread | |
|
Instances
Growth | |
|
Instances
FromJSON Growth Source # | |
Defined in Swarm.Game.Entity | |
ToJSON Growth Source # | |
Generic Growth Source # | |
Read Growth Source # | |
Show Growth Source # | |
Eq Growth Source # | |
Ord Growth Source # | |
Hashable Growth Source # | |
Defined in Swarm.Game.Entity | |
type Rep Growth Source # | |
Defined in Swarm.Game.Entity type Rep Growth = D1 ('MetaData "Growth" "Swarm.Game.Entity" "swarm-0.6.0.0-ERx1HMcRMba59aI2b6aNrS-swarm-scenario" 'False) (C1 ('MetaCons "Growth" 'PrefixI 'True) (S1 ('MetaSel ('Just "maturesTo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe EntityName)) :*: (S1 ('MetaSel ('Just "growthSpread") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe GrowthSpread)) :*: S1 ('MetaSel ('Just "growthTime") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 GrowthTime)))) |
data Combustibility Source #
Properties of combustion.
Combustibility | |
|
Instances
defaultCombustibility :: Combustibility Source #
The default combustion specification for a combustible entity with no combustion specification:
- ignition rate 0.5
- duration (100, 200)
- product
ash
Entities
A record to hold information about an entity.
The constructor for Entity
is intentionally not exported. To
construct one manually, use the mkEntity
function.
There are two main constraints on the way entities are stored:
- We want to be able to easily modify an entity in one particular cell of the world (for example, painting one tree red).
- In an inventory, we want to store identical entities only once, along with a count.
We could get (2) nicely by storing only names of entities, and having a global lookup table from names to entity records. However, storing names instead of actual entity records in the world makes (1) more complex: every time we modify an entity we would have to generate a fresh name for the modified entity and add it to the global entity table. This approach is also annoying because it means we can't just uses lenses to drill down into the properties of an entity in the world or in an inventory, but have to do an intermediate lookup in the global (mutable!) entity table.
On the other hand, if we just store entity records everywhere, checking them for equality becomes expensive. Having an inventory be a map with entities themselves as keys sounds awful.
The solution we adopt here is that every Entity
record carries
along a hash value of all the other fields. We just assume that
these hashes are unique (a collision is of course possible but
extremely unlikely). Entities can be efficiently compared just
by looking at their hashes; they can be stored in a map using
hash values as keys; and we provide lenses which automatically
recompute the hash value when modifying a field of an entity
record. Note also that world storage is still efficient, too:
thanks to referential transparency, in practice most of the
entities stored in the world that are the same will literally
just be stored as pointers to the same shared record.
Instances
:: Display | Display |
-> Text | Entity name |
-> Document Syntax | Entity description |
-> [EntityProperty] | Properties |
-> Set Capability | Capabilities |
-> Entity |
Create an entity with no orientation, an empty inventory, providing no capabilities (automatically filling in the hash value).
Fields
Our own custom lenses which properly recompute the cached hash value each time something gets updated. See https://byorgey.wordpress.com/2021/09/17/automatically-updated-cached-views-with-lens/ for the approach used here.
entityDisplay :: Lens' Entity Display Source #
The Display
explaining how to draw this entity in the world display.
entityName :: Lens' Entity EntityName Source #
The name of the entity.
entityPlural :: Lens' Entity (Maybe Text) Source #
The irregular plural version of the entity's name, if there is one.
entityNameFor :: Int -> Getter Entity Text Source #
Get a version of the entity's name appropriate to the number---the singular name for 1, and a plural name for any other number. The plural name is obtained either by looking it up if irregular, or by applying standard heuristics otherwise.
entityDescription :: Lens' Entity (Document Syntax) Source #
A longer, free-form description of the entity. Each Text
value
represents a paragraph.
entityOrientation :: Lens' Entity (Maybe Heading) Source #
The direction this entity is facing (if it has one).
entityGrowth :: Lens' Entity (Maybe Growth) Source #
How long this entity takes to grow, if it regrows.
entityCombustion :: Lens' Entity (Maybe Combustibility) Source #
Susceptibility to and duration of combustion
entityYields :: Lens' Entity (Maybe Text) Source #
The name of a different entity yielded when this entity is grabbed, if any.
entityProperties :: Lens' Entity (Set EntityProperty) Source #
The properties enjoyed by this entity.
hasProperty :: Entity -> EntityProperty -> Bool Source #
Test whether an entity has a certain property.
entityCapabilities :: Lens' Entity (SingleEntityCapabilities EntityName) Source #
The capabilities this entity provides when equipped.
entityBiomes :: Lens' Entity (Set TerrainType) Source #
The inventory of other entities carried by this entity.
entityInventory :: Lens' Entity Inventory Source #
The inventory of other entities carried by this entity.
entityHash :: Getter Entity Int Source #
Get the hash of an entity. Note that this is a getter, not a lens; the Swarm.Game.Entity module carefully maintains some internal invariants ensuring that hashes work properly, and by golly, no one else is going to mess that up.
Entity map
An EntityMap
is a data structure containing all the loaded
entities, allowing them to be looked up either by name or by what
capabilities they provide (if any).
Also preserves the original definition order from the scenario
file and canonical definition list.
This enables scenario authors to specify iteration order of
the TagMembers
command.
Instances
ToJSON EntityMap Source # | |
Monoid EntityMap Source # | |
Semigroup EntityMap Source # | Note that duplicates in a single |
Generic EntityMap Source # | |
Show EntityMap Source # | |
Eq EntityMap Source # | |
FromJSONE EntityMap Entity Source # | If we have access to an |
Defined in Swarm.Game.Entity parseJSONE :: Value -> ParserE EntityMap Entity parseJSONE' :: EntityMap -> Value -> Parser Entity | |
FromJSONE EntityMap (Recipe Entity) | |
Defined in Swarm.Game.Recipe | |
type Rep EntityMap Source # | |
Defined in Swarm.Game.Entity type Rep EntityMap = D1 ('MetaData "EntityMap" "Swarm.Game.Entity" "swarm-0.6.0.0-ERx1HMcRMba59aI2b6aNrS-swarm-scenario" 'False) (C1 ('MetaCons "EntityMap" 'PrefixI 'True) (S1 ('MetaSel ('Just "entitiesByName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Map EntityName Entity)) :*: (S1 ('MetaSel ('Just "entitiesByCap") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (MultiEntityCapabilities Entity Entity)) :*: S1 ('MetaSel ('Just "entityDefinitionOrder") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Entity])))) |
buildEntityMap :: Has (Throw LoadingFailure) sig m => [Entity] -> m EntityMap Source #
Build an EntityMap
from a list of entities. The idea is that
this will be called once at startup, when loading the entities
from a file; see loadEntities
.
validateEntityAttrRefs :: Has (Throw LoadingFailure) sig m => Set WorldAttr -> [Entity] -> m () Source #
Validates references to Display
attributes
loadEntities :: (Has (Throw SystemFailure) sig m, Has (Lift IO) sig m) => m EntityMap Source #
Load entities from a data file called entities.yaml
, producing
either an EntityMap
or a parse error.
allEntities :: EntityMap -> [Entity] Source #
Get a list of all the entities in the entity map.
devicesForCap :: Capability -> EntityMap -> [Entity] Source #
Find all entities which are devices that provide the given capability.
Inventories
An inventory is really just a bag/multiset of entities. That is, it contains some entities, along with the number of times each occurs. Entities can be looked up directly, or by name.
Instances
FromJSON Inventory Source # | |
Defined in Swarm.Game.Entity | |
ToJSON Inventory Source # | |
Generic Inventory Source # | |
Show Inventory Source # | |
Eq Inventory Source # | Inventories are compared by hash for efficiency. |
Hashable Inventory Source # | |
Defined in Swarm.Game.Entity | |
type Rep Inventory Source # | |
Defined in Swarm.Game.Entity type Rep Inventory = D1 ('MetaData "Inventory" "Swarm.Game.Entity" "swarm-0.6.0.0-ERx1HMcRMba59aI2b6aNrS-swarm-scenario" 'False) (C1 ('MetaCons "Inventory" 'PrefixI 'True) (S1 ('MetaSel ('Just "counts") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (IntMap (Count, Entity))) :*: (S1 ('MetaSel ('Just "byName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Map Text IntSet)) :*: S1 ('MetaSel ('Just "inventoryHash") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int)))) |
Construction
fromElems :: [(Count, Entity)] -> Inventory Source #
Create an inventory from a list of entities and their counts.
Lookup
lookup :: Entity -> Inventory -> Count Source #
Look up an entity in an inventory, returning the number of copies contained.
lookupByName :: Text -> Inventory -> [Entity] Source #
Look up an entity by name in an inventory, returning a list of
matching entities. Note, if this returns some entities, it does
not mean we necessarily have any in our inventory! It just
means we know about them. If you want to know whether you have
any, use lookup
and see whether the resulting Count
is
positive, or just use countByName
in the first place.
countByName :: Text -> Inventory -> Count Source #
Look up an entity by name and see how many there are in the
inventory. If there are multiple entities with the same name, it
just picks the first one returned from lookupByName
.
contains :: Inventory -> Entity -> Bool Source #
Check whether an inventory contains at least one of a given entity.
contains0plus :: Entity -> Inventory -> Bool Source #
Check whether an inventory has an entry for the given entity, even if there are 0 copies. In particular this is used to indicate whether a robot "knows about" an entity.
elems :: Inventory -> [(Count, Entity)] Source #
Get the entities in an inventory and their associated counts.
isSubsetOf :: Inventory -> Inventory -> Bool Source #
Check if the first inventory is a subset of the second. Note that entities with a count of 0 are ignored.
isEmpty :: Inventory -> Bool Source #
Check whether an inventory is empty, meaning that it contains 0 total entities (although it may still know about some entities, that is, have them as keys with a count of 0).
inventoryCapabilities :: Inventory -> MultiEntityCapabilities Entity EntityName Source #
Compute the set of capabilities provided by the devices in an inventory.
extantElemsWithCapability :: Capability -> Inventory -> [Entity] Source #
List elements that possess a given Capability and exist with nonzero count in the inventory.
entitiesByCapability :: Inventory -> Map Capability (NonEmpty Entity) Source #
Groups entities by the capabilities they offer.
Modification
insert :: Entity -> Inventory -> Inventory Source #
Insert an entity into an inventory. If the inventory already contains this entity, then only its count will be incremented.
insertCount :: Count -> Entity -> Inventory -> Inventory Source #
Insert a certain number of copies of an entity into an inventory. If the inventory already contains this entity, then only its count will be incremented.
delete :: Entity -> Inventory -> Inventory Source #
Delete a single copy of a certain entity from an inventory.
deleteCount :: Count -> Entity -> Inventory -> Inventory Source #
Delete a specified number of copies of an entity from an inventory.