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

Swarm.Game.State

Description

Definition of the record holding all the game-related state, and various related utility functions.

Synopsis

Game state record and related types

data ViewCenterRule Source #

The ViewCenterRule specifies how to determine the center of the world viewport.

Constructors

VCLocation (Cosmic Location)

The view should be centered on an absolute position.

VCRobot RID

The view should be centered on a certain robot.

Instances

Instances details
FromJSON ViewCenterRule Source # 
Instance details

Defined in Swarm.Game.State

ToJSON ViewCenterRule Source # 
Instance details

Defined in Swarm.Game.State

Generic ViewCenterRule Source # 
Instance details

Defined in Swarm.Game.State

Associated Types

type Rep ViewCenterRule :: Type -> Type #

Show ViewCenterRule Source # 
Instance details

Defined in Swarm.Game.State

Eq ViewCenterRule Source # 
Instance details

Defined in Swarm.Game.State

Ord ViewCenterRule Source # 
Instance details

Defined in Swarm.Game.State

type Rep ViewCenterRule Source # 
Instance details

Defined in Swarm.Game.State

type Rep ViewCenterRule = D1 ('MetaData "ViewCenterRule" "Swarm.Game.State" "swarm-0.5.0.0-6qXEbhCmuXA4wRndqqhBu" 'False) (C1 ('MetaCons "VCLocation" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Cosmic Location))) :+: C1 ('MetaCons "VCRobot" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 RID)))

data REPLStatus Source #

A data type to represent the current status of the REPL.

Constructors

REPLDone (Maybe (Typed Value))

The REPL is not doing anything actively at the moment. We persist the last value and its type though.

INVARIANT: the Value stored here is not a VResult.

REPLWorking (Typed (Maybe Value))

A command entered at the REPL is currently being run. The Polytype represents the type of the expression that was entered. The Maybe Value starts out as Nothing and gets filled in with a result once the command completes.

Instances

Instances details
FromJSON REPLStatus Source # 
Instance details

Defined in Swarm.Game.State

ToJSON REPLStatus Source # 
Instance details

Defined in Swarm.Game.State

Generic REPLStatus Source # 
Instance details

Defined in Swarm.Game.State

Associated Types

type Rep REPLStatus :: Type -> Type #

Show REPLStatus Source # 
Instance details

Defined in Swarm.Game.State

Eq REPLStatus Source # 
Instance details

Defined in Swarm.Game.State

type Rep REPLStatus Source # 
Instance details

Defined in Swarm.Game.State

type Rep REPLStatus = D1 ('MetaData "REPLStatus" "Swarm.Game.State" "swarm-0.5.0.0-6qXEbhCmuXA4wRndqqhBu" 'False) (C1 ('MetaCons "REPLDone" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe (Typed Value)))) :+: C1 ('MetaCons "REPLWorking" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Typed (Maybe Value)))))

data WinStatus Source #

Constructors

Ongoing

There are one or more objectives remaining that the player has not yet accomplished.

Won Bool

The player has won. The boolean indicates whether they have already been congratulated.

Unwinnable Bool

The player has completed certain "goals" that preclude (via negative prerequisites) the completion of all of the required goals. The boolean indicates whether they have already been informed.

Instances

Instances details
FromJSON WinStatus Source # 
Instance details

Defined in Swarm.Game.State

ToJSON WinStatus Source # 
Instance details

Defined in Swarm.Game.State

Generic WinStatus Source # 
Instance details

Defined in Swarm.Game.State

Associated Types

type Rep WinStatus :: Type -> Type #

Show WinStatus Source # 
Instance details

Defined in Swarm.Game.State

type Rep WinStatus Source # 
Instance details

Defined in Swarm.Game.State

type Rep WinStatus = D1 ('MetaData "WinStatus" "Swarm.Game.State" "swarm-0.5.0.0-6qXEbhCmuXA4wRndqqhBu" 'False) (C1 ('MetaCons "Ongoing" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Won" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Bool)) :+: C1 ('MetaCons "Unwinnable" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Bool))))

data WinCondition Source #

Constructors

NoWinCondition

There is no winning condition.

WinConditions WinStatus ObjectiveCompletion

NOTE: It is possible to continue to achieve "optional" objectives even after the game has been won (or deemed unwinnable).

Instances

Instances details
FromJSON WinCondition Source # 
Instance details

Defined in Swarm.Game.State

ToJSON WinCondition Source # 
Instance details

Defined in Swarm.Game.State

Generic WinCondition Source # 
Instance details

Defined in Swarm.Game.State

Associated Types

type Rep WinCondition :: Type -> Type #

Show WinCondition Source # 
Instance details

Defined in Swarm.Game.State

ToSample WinCondition Source # 
Instance details

Defined in Swarm.Game.State

type Rep WinCondition Source # 
Instance details

Defined in Swarm.Game.State

type Rep WinCondition = D1 ('MetaData "WinCondition" "Swarm.Game.State" "swarm-0.5.0.0-6qXEbhCmuXA4wRndqqhBu" 'False) (C1 ('MetaCons "NoWinCondition" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "WinConditions" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 WinStatus) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ObjectiveCompletion)))

data ObjectiveCompletion Source #

Constructors

ObjectiveCompletion 

Fields

  • completionBuckets :: CompletionBuckets

    This is the authoritative "completion status" for all objectives. Note that there is a separate Set to store the completion status of prerequisite objectives, which must be carefully kept in sync with this. Those prerequisite objectives are required to have labels, but other objectives are not. Therefore only prerequisites exist in the completion map keyed by label.

  • completedIDs :: Set ObjectiveLabel
     

Instances

Instances details
FromJSON ObjectiveCompletion Source # 
Instance details

Defined in Swarm.Game.Scenario.Objective

ToJSON ObjectiveCompletion Source # 
Instance details

Defined in Swarm.Game.Scenario.Objective

Generic ObjectiveCompletion Source # 
Instance details

Defined in Swarm.Game.Scenario.Objective

Associated Types

type Rep ObjectiveCompletion :: Type -> Type #

Show ObjectiveCompletion Source # 
Instance details

Defined in Swarm.Game.Scenario.Objective

type Rep ObjectiveCompletion Source # 
Instance details

Defined in Swarm.Game.Scenario.Objective

type Rep ObjectiveCompletion = D1 ('MetaData "ObjectiveCompletion" "Swarm.Game.Scenario.Objective" "swarm-0.5.0.0-6qXEbhCmuXA4wRndqqhBu" 'False) (C1 ('MetaCons "ObjectiveCompletion" 'PrefixI 'True) (S1 ('MetaSel ('Just "completionBuckets") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 CompletionBuckets) :*: S1 ('MetaSel ('Just "completedIDs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Set ObjectiveLabel))))

newtype Announcement Source #

TODO: #1044 Could also add an ObjectiveFailed constructor...

Instances

Instances details
ToJSON Announcement Source # 
Instance details

Defined in Swarm.Game.Scenario.Objective

Generic Announcement Source # 
Instance details

Defined in Swarm.Game.Scenario.Objective

Associated Types

type Rep Announcement :: Type -> Type #

Show Announcement Source # 
Instance details

Defined in Swarm.Game.Scenario.Objective

type Rep Announcement Source # 
Instance details

Defined in Swarm.Game.Scenario.Objective

type Rep Announcement = D1 ('MetaData "Announcement" "Swarm.Game.Scenario.Objective" "swarm-0.5.0.0-6qXEbhCmuXA4wRndqqhBu" 'True) (C1 ('MetaCons "ObjectiveCompleted" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Objective)))

data RunStatus Source #

A data type to keep track of the pause mode.

Constructors

Running

The game is running.

ManualPause

The user paused the game, and it should stay pause after visiting the help.

AutoPause

The game got paused while visiting the help, and it should unpause after returning back to the game.

Instances

Instances details
FromJSON RunStatus Source # 
Instance details

Defined in Swarm.Game.State

ToJSON RunStatus Source # 
Instance details

Defined in Swarm.Game.State

Generic RunStatus Source # 
Instance details

Defined in Swarm.Game.State

Associated Types

type Rep RunStatus :: Type -> Type #

Show RunStatus Source # 
Instance details

Defined in Swarm.Game.State

Eq RunStatus Source # 
Instance details

Defined in Swarm.Game.State

type Rep RunStatus Source # 
Instance details

Defined in Swarm.Game.State

type Rep RunStatus = D1 ('MetaData "RunStatus" "Swarm.Game.State" "swarm-0.5.0.0-6qXEbhCmuXA4wRndqqhBu" 'False) (C1 ('MetaCons "Running" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ManualPause" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AutoPause" 'PrefixI 'False) (U1 :: Type -> Type)))

type Seed = Int Source #

data Step Source #

Game step mode - we use the single step mode when debugging robot CESK machine.

data SingleStep Source #

Type for remembering which robots will be run next in a robot step mode.

Once some robots have run, we need to store RID to know which ones should go next. At SBefore no robots were run yet, so it is safe to transition to and from WorldTick.

                    tick
    ┌────────────────────────────────────┐
    │                                    │
    │               step                 │
    │              ┌────┐                │
    ▼              ▼    │                │
┌───────┐ step  ┌───────┴───┐ step  ┌────┴─────┐
│SBefore├──────►│SSingle RID├──────►│SAfter RID│
└──┬────┘       └───────────┘       └────┬─────┘
   │ ▲ player        ▲                   │
   ▼ │ switch        └───────────────────┘
┌────┴────┐             view RID > oldRID
│WorldTick│
└─────────┘

Constructors

SBefore

Run the robots from the beginning until the focused robot (noninclusive).

SSingle RID

Run a single step of the focused robot.

SAfter RID

Run robots after the (previously) focused robot and finish the tick.

data GameState Source #

The main record holding the state for the game itself (as distinct from the UI). See the lenses below for access to its fields.

GameState fields

creativeMode :: Lens' GameState Bool Source #

Is the user in creative mode (i.e. able to do anything without restriction)?

winCondition :: Lens' GameState WinCondition Source #

How to determine whether the player has won.

winSolution :: Lens' GameState (Maybe ProcessedTerm) Source #

How to win (if possible). This is useful for automated testing and to show help to cheaters (or testers).

robotMap :: Lens' GameState (IntMap Robot) Source #

All the robots that currently exist in the game, indexed by ID.

robotsByLocation :: Lens' GameState (Map SubworldName (Map Location IntSet)) Source #

The names of all robots that currently exist in the game, indexed by location (which we need both for e.g. the salvage command as well as for actually drawing the world). Unfortunately there is no good way to automatically keep this up to date, since we don't just want to completely rebuild it every time the robotMap changes. Instead, we just make sure to update it every time the location of a robot changes, or a robot is created or destroyed. Fortunately, there are relatively few ways for these things to happen.

robotsAtLocation :: Cosmic Location -> GameState -> [Robot] Source #

Get a list of all the robots at a particular location.

robotsWatching :: Lens' GameState (Map (Cosmic Location) (Set RID)) Source #

Get a list of all the robots that are "watching" by location.

robotsInArea :: Cosmic Location -> Int32 -> GameState -> [Robot] Source #

Get all the robots within a given Manhattan distance from a location.

baseRobot :: Traversal' GameState Robot Source #

The base robot, if it exists.

activeRobots :: Getter GameState IntSet Source #

The names of the robots that are currently not sleeping.

waitingRobots :: Getter GameState (Map TickNumber [RID]) Source #

The names of the robots that are currently sleeping, indexed by wake up time. Note that this may not include all sleeping robots, particularly those that are only taking a short nap (e.g. wait 1).

messageNotifications :: Getter GameState (Notifications LogEntry) Source #

Get the notification list of messages from the point of view of focused robot.

seed :: Lens' GameState Seed Source #

The initial seed that was used for the random number generator, and world generation.

randGen :: Lens' GameState StdGen Source #

Pseudorandom generator initialized at start.

currentScenarioPath :: Lens' GameState (Maybe FilePath) Source #

The filepath of the currently running scenario.

This is useful as an index to the scenarios collection, see scenarioItemByPath.

viewCenterRule :: Lens' GameState ViewCenterRule Source #

The current rule for determining the center of the world view. It updates also, viewCenter and focusedRobot to keep everything synchronized.

viewCenter :: Getter GameState (Cosmic Location) Source #

The current center of the world view. Note that this cannot be modified directly, since it is calculated automatically from the viewCenterRule. To modify the view center, either set the viewCenterRule, or use modifyViewCenter.

needsRedraw :: Lens' GameState Bool Source #

Whether the world view needs to be redrawn.

focusedRobotID :: Getter GameState RID Source #

The current robot in focus.

It is only a Getter because this value should be updated only when the viewCenterRule is specified to be a robot.

Technically it's the last robot ID specified by viewCenterRule, but that robot may not be alive anymore - to be safe use focusedRobot.

Subrecord accessors

temporal :: Lens' GameState TemporalState Source #

Aspects of the temporal state of the game

robotNaming :: Lens' GameState RobotNaming Source #

State and data for assigning identifiers to robots

recipesInfo :: Lens' GameState Recipes Source #

Collection of recipe info

gameControls :: Lens' GameState GameControls Source #

Controls, including REPL and key mapping

discovery :: Lens' GameState Discovery Source #

Discovery state of entities, commands, recipes

landscape :: Lens' GameState Landscape Source #

Info about the lay of the land

GameState subrecords

Temporal state

gameStep :: Lens' TemporalState Step Source #

How to step the game: WorldTick or RobotStep for debugging the CESK machine.

ticks :: Lens' TemporalState TickNumber Source #

The number of ticks elapsed since the game started.

robotStepsPerTick :: Lens' TemporalState Int Source #

The maximum number of CESK machine steps a robot may take during a single tick.

paused :: Getter TemporalState Bool Source #

Whether the game is currently paused.

Robot naming

gensym :: Lens' RobotNaming Int Source #

A counter used to generate globally unique IDs.

Recipes

recipesOut :: Lens' Recipes (IntMap [Recipe Entity]) Source #

All recipes the game knows about, indexed by outputs.

recipesIn :: Lens' Recipes (IntMap [Recipe Entity]) Source #

All recipes the game knows about, indexed by inputs.

recipesCat :: Lens' Recipes (IntMap [Recipe Entity]) Source #

All recipes the game knows about, indexed by requirement/catalyst.

Messages

messageQueue :: Lens' Messages (Seq LogEntry) Source #

A queue of global messages.

Note that we put the newest entry to the right.

lastSeenMessageTime :: Lens' Messages TickNumber Source #

Last time message queue has been viewed (used for notification).

announcementQueue :: Lens' Messages (Seq Announcement) Source #

A queue of global announcements. Note that this is distinct from the messageQueue, which is for messages emitted by robots.

Note that we put the newest entry to the right.

Controls

initiallyRunCode :: Lens' GameControls (Maybe ProcessedTerm) Source #

Code that is run upon scenario start, before any REPL interaction.

replStatus :: Lens' GameControls REPLStatus Source #

The current status of the REPL.

replNextValueIndex :: Lens' GameControls Integer Source #

The index of the next it{index} value

replWorking :: Getter GameControls Bool Source #

Whether the repl is currently working.

replActiveType :: Getter REPLStatus (Maybe Polytype) Source #

Either the type of the command being executed, or of the last command

inputHandler :: Lens' GameControls (Maybe (Text, Value)) Source #

The currently installed input handler and hint text.

Discovery

allDiscoveredEntities :: Lens' Discovery Inventory Source #

The list of entities that have been discovered.

availableRecipes :: Lens' Discovery (Notifications (Recipe Entity)) Source #

The list of available recipes.

availableCommands :: Lens' Discovery (Notifications Const) Source #

The list of available commands.

knownEntities :: Lens' Discovery [Text] Source #

The names of entities that should be considered "known", that is, robots know what they are without having to scan them.

gameAchievements :: Lens' Discovery (Map GameplayAchievement Attainment) Source #

Map of in-game achievements that were obtained

Landscape

worldNavigation :: Lens' Landscape (Navigation (Map SubworldName) Location) Source #

Includes a Map of named locations and an "edge list" (graph) that maps portal entrances to exits

multiWorld :: Lens' Landscape (MultiWorld Int Entity) Source #

The current state of the world (terrain and entities only; robots are stored in the robotMap). Int is used instead of TerrainType because we need to be able to store terrain values in unboxed tile arrays.

worldScrollable :: Lens' Landscape Bool Source #

Whether the world map is supposed to be scrollable or not.

entityMap :: Lens' Landscape EntityMap Source #

The catalog of all entities that the game knows about.

Notifications

data Notifications a Source #

A data type to keep track of some kind of log or sequence, with an index to remember which ones are "new" and which ones have "already been seen".

Instances

Instances details
FromJSON a => FromJSON (Notifications a) Source # 
Instance details

Defined in Swarm.Game.State

ToJSON a => ToJSON (Notifications a) Source # 
Instance details

Defined in Swarm.Game.State

Monoid (Notifications a) Source # 
Instance details

Defined in Swarm.Game.State

Semigroup (Notifications a) Source # 
Instance details

Defined in Swarm.Game.State

Generic (Notifications a) Source # 
Instance details

Defined in Swarm.Game.State

Associated Types

type Rep (Notifications a) :: Type -> Type #

Show a => Show (Notifications a) Source # 
Instance details

Defined in Swarm.Game.State

Eq a => Eq (Notifications a) Source # 
Instance details

Defined in Swarm.Game.State

type Rep (Notifications a) Source # 
Instance details

Defined in Swarm.Game.State

type Rep (Notifications a) = D1 ('MetaData "Notifications" "Swarm.Game.State" "swarm-0.5.0.0-6qXEbhCmuXA4wRndqqhBu" 'False) (C1 ('MetaCons "Notifications" 'PrefixI 'True) (S1 ('MetaSel ('Just "_notificationsCount") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Just "_notificationsContent") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [a])))

Launch parameters

type ValidatedLaunchParams = LaunchParams Identity Source #

In this stage in the UI pipeline, both fields have already been validated, and Nothing means that the field is simply absent.

GameState initialization

data GameStateConfig Source #

Record to pass information needed to create an initial GameState record when starting a scenario.

initGameState :: GameStateConfig -> GameState Source #

Create an initial, fresh game state record when starting a new scenario.

scenarioToGameState :: Scenario -> ValidatedLaunchParams -> GameStateConfig -> IO GameState Source #

Create an initial game state corresponding to the given scenario.

newtype Sha1 Source #

Constructors

Sha1 String 

data SolutionSource Source #

Constructors

ScenarioSuggested 
PlayerAuthored FilePath Sha1

Includes the SHA1 of the program text for the purpose of corroborating solutions on a leaderboard.

Utilities

applyViewCenterRule :: ViewCenterRule -> IntMap Robot -> Maybe (Cosmic Location) Source #

Given a current mapping from robot names to robots, apply a ViewCenterRule to derive the location it refers to. The result is Maybe because the rule may refer to a robot which does not exist.

recalcViewCenter :: GameState -> GameState Source #

Recalculate the view center (and cache the result in the viewCenter field) based on the current viewCenterRule. If the viewCenterRule specifies a robot which does not exist, simply leave the current viewCenter as it is. Set needsRedraw if the view center changes.

modifyViewCenter :: (Cosmic Location -> Cosmic Location) -> GameState -> GameState Source #

Modify the viewCenter by applying an arbitrary function to the current value. Note that this also modifies the viewCenterRule to match. After calling this function the viewCenterRule will specify a particular location, not a robot.

viewingRegion :: Cosmic Location -> (Int32, Int32) -> Cosmic BoundsRectangle Source #

Given a width and height, compute the region, centered on the viewCenter, that should currently be in view.

unfocus :: GameState -> GameState Source #

Unfocus by modifying the view center rule to look at the current location instead of a specific robot, and also set the focused robot ID to an invalid value. In classic mode this causes the map view to become nothing but static.

focusedRobot :: GameState -> Maybe Robot Source #

Find out which robot has been last specified by the viewCenterRule, if any.

data RobotRange Source #

Type for describing how far away a robot is from the base, which determines what kind of communication can take place.

Constructors

Close

Close; communication is perfect.

MidRange Double

Mid-range; communication is possible but lossy.

Far

Far; communication is not possible.

focusedRange :: GameState -> Maybe RobotRange Source #

Check how far away the focused robot is from the base. Nothing is returned if there is no focused robot; otherwise, return a RobotRange value as follows.

  • If we are in creative or scroll-enabled mode, the focused robot is always considered Close.
  • Otherwise, there is a "minimum radius" and "maximum radius".

    • If the robot is within the minimum radius, it is Close.
    • If the robot is between the minimum and maximum radii, it is MidRange, with a Double value ranging linearly from 0 to 1 proportional to the distance from the minimum to maximum radius. For example, MidRange 0.5 would indicate a robot exactly halfway between the minimum and maximum radii.
    • If the robot is beyond the maximum radius, it is Far.
  • By default, the minimum radius is 16, and maximum is 64.
  • Device augmentations

    • If the focused robot has an antenna installed, it doubles both radii.
    • If the base has an antenna installed, it also doubles both radii.

getRadioRange :: Maybe Robot -> Maybe Robot -> (Double, Double) Source #

Get the min/max communication radii given possible augmentations on each end

clearFocusedRobotLogUpdated :: Has (State GameState) sig m => m () Source #

Clear the robotLogUpdated flag of the focused robot.

addRobot :: Has (State GameState) sig m => Robot -> m () Source #

Add a robot to the game state, adding it to the main robot map, the active robot set, and to to the index of robots by location.

addRobotToLocation :: Has (State GameState) sig m => RID -> Cosmic Location -> m () Source #

Helper function for updating the "robotsByLocation" bookkeeping

addTRobot :: Has (State GameState) sig m => TRobot -> m Robot Source #

Add a concrete instance of a robot template to the game state: First, generate a unique ID number for it. Then, add it to the main robot map, the active robot set, and to to the index of robots by location. Return the updated robot.

emitMessage :: Has (State GameState) sig m => LogEntry -> m () Source #

Add a message to the message queue.

wakeWatchingRobots :: Has (State GameState) sig m => Cosmic Location -> m () Source #

Iterates through all of the currently wait-ing robots, and moves forward the wake time of the ones that are watch-ing this location.

NOTE: Clearing TickNumber map entries from internalWaitingRobots upon wakeup is handled by wakeUpRobotsDoneSleeping

sleepUntil :: Has (State GameState) sig m => RID -> TickNumber -> m () Source #

Takes a robot out of the activeRobots set and puts it in the waitingRobots queue.

sleepForever :: Has (State GameState) sig m => RID -> m () Source #

Takes a robot out of the activeRobots set.

wakeUpRobotsDoneSleeping :: Has (State GameState) sig m => m () Source #

Removes robots whose wake up time matches the current game ticks count from the waitingRobots queue and put them back in the activeRobots set if they still exist in the keys of robotMap.

deleteRobot :: Has (State GameState) sig m => RID -> m () Source #

removeRobotFromLocationMap :: Has (State GameState) sig m => Cosmic Location -> RID -> m () Source #

Makes sure empty sets don't hang around in the robotsByLocation map. We don't want a key with an empty set at every location any robot has ever visited!

activateRobot :: Has (State GameState) sig m => RID -> m () Source #

Adds a robot to the activeRobots set.

toggleRunStatus :: RunStatus -> RunStatus Source #

Switch (auto or manually) paused game to running and running to manually paused.

Note that this function is not safe to use in the app directly, because the UI also tracks time between ticks---use safeTogglePause instead.

messageIsFromNearby :: Cosmic Location -> LogEntry -> Bool Source #

Reconciles the possibilities of log messages being omnipresent and robots being in different worlds

buildWorldTuples :: Scenario -> NonEmpty SubworldDescription Source #

genMultiWorld :: NonEmpty SubworldDescription -> Seed -> MultiWorld Int Entity Source #

genRobotTemplates :: Scenario -> NonEmpty (a, ([(Int, TRobot)], b)) -> [TRobot] Source #

Returns a list of robots, ordered by decreasing preference to serve as the "base".

Rules for selecting the "base" robot:

What follows is a thorough description of how the base choice is made as of the most recent study of the code. This level of detail is not meant to be public-facing.

For an abbreviated explanation, see the "Base robot" section of the Scenario Authoring Guide.

Precedence rules

  1. Prefer those robots defined with a loc (robotLocation) in the scenario file

    1. If multiple robots define a loc, use the robot that is defined first within the scenario file.
    2. Note that if a robot is both given a loc AND is specified in the world map, then two instances of the robot shall be created. The instance with the loc shall be preferred as the base.
  1. Fall back to robots generated from templates via the map and palette.

    1. If multiple robots are specified in the map, prefer the one that is defined first within the scenario file.
    2. If multiple robots are instantiated from the same template, then prefer the one with a lower-indexed subworld. Note that the root subworld is always first.
    3. If multiple robots instantiated from the same template are in the same subworld, then prefer the one closest to the upper-left of the screen, with higher rows given precedence over columns (i.e. first in row-major order).