swarm-0.2.0.0: 2D resource gathering game with programmable robots
CopyrightBrent Yorgey
LicenseBSD-3-Clause
Maintainerbyorgey@gmail.com
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 (V2 Int64)

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.2.0.0-D1mAmWsUEjoFqpCaq9DHG0" 'False) (C1 ('MetaCons "VCLocation" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (V2 Int64))) :+: 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.

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.2.0.0-D1mAmWsUEjoFqpCaq9DHG0" '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 WinCondition Source #

Constructors

NoWinCondition

There is no winning condition.

WinConditions (NonEmpty Objective)

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.

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

type Rep WinCondition Source # 
Instance details

Defined in Swarm.Game.State

type Rep WinCondition = D1 ('MetaData "WinCondition" "Swarm.Game.State" "swarm-0.2.0.0-D1mAmWsUEjoFqpCaq9DHG0" 'False) (C1 ('MetaCons "NoWinCondition" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "WinConditions" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (NonEmpty Objective))) :+: C1 ('MetaCons "Won" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Bool))))

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.2.0.0-D1mAmWsUEjoFqpCaq9DHG0" '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 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).

paused :: Getter GameState Bool Source #

Whether the game is currently paused.

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

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

robotsByLocation :: Lens' GameState (Map (V2 Int64) 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 :: V2 Int64 -> GameState -> [Robot] Source #

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

robotsInArea :: V2 Int64 -> Int64 -> GameState -> [Robot] Source #

Get robots in manhattan distastance from 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 Integer [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).

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

The list of available recipes.

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

The list of available commands.

messageNotifications :: Getter GameState (Notifications LogEntry) Source #

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

allDiscoveredEntities :: Lens' GameState Inventory Source #

The list of entities that have been discovered.

gensym :: Lens' GameState Int Source #

A counter used to generate globally unique IDs.

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.

adjList :: Getter GameState (Array Int Text) Source #

Read-only list of words, for use in building random robot names.

nameList :: Getter GameState (Array Int Text) Source #

Read-only list of words, for use in building random robot names.

entityMap :: Lens' GameState EntityMap Source #

The catalog of all entities that the game knows about.

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

All recipes the game knows about, indexed by outputs.

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

All recipes the game knows about, indexed by inputs.

recipesReq :: Lens' GameState (IntMap [Recipe Entity]) Source #

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

scenarios :: Lens' GameState ScenarioCollection Source #

The collection of scenarios that comes with the game.

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

The filepath of the currently running scenario.

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

knownEntities :: Lens' GameState [Text] Source #

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

world :: Lens' GameState (World 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.

viewCenterRule :: Lens' GameState ViewCenterRule Source #

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

viewCenter :: Getter GameState (V2 Int64) 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.

replStatus :: Lens' GameState REPLStatus Source #

The current status of the REPL.

replNextValueIndex :: Lens' GameState Integer Source #

The index of the next it{index} value

replWorking :: Getter GameState 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

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

A queue of global messages.

Note that we put the newest entry to the right.

lastSeenMessageTime :: Lens' GameState Integer Source #

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

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.

ticks :: Lens' GameState Integer Source #

The number of ticks elapsed since the game started.

robotStepsPerTick :: Lens' GameState Int Source #

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

Notifications

data Notifications a Source #

A data type to keep track of discovered recipes and commands

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.2.0.0-D1mAmWsUEjoFqpCaq9DHG0" 'False) (C1 ('MetaCons "Notifications" 'PrefixI 'True) (S1 ('MetaSel ('Just "_notificationsCount") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Just "_notificationsContent") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [a])))

GameState initialization

initGameState :: ExceptT Text IO GameState Source #

Create an initial game state record, first loading entities and recipies from disk.

scenarioToGameState :: Scenario -> Maybe Seed -> Maybe CodeToRun -> GameState -> IO GameState Source #

Set a given scenario as the currently loaded scenario in the game state.

initGameStateForScenario :: String -> Maybe Seed -> Maybe FilePath -> ExceptT Text IO GameState Source #

Create an initial game state for a specific scenario. Note that this function is used only for unit tests, integration tests, and benchmarks.

In normal play, the code path that gets executed is scenarioToAppState.

classicGame0 :: ExceptT Text IO GameState Source #

For convenience, the GameState corresponding to the classic game with seed 0. This is used only for benchmarks and unit tests.

Utilities

applyViewCenterRule :: ViewCenterRule -> IntMap Robot -> Maybe (V2 Int64) 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 veiw 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 :: (V2 Int64 -> V2 Int64) -> 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 :: GameState -> (Int64, Int64) -> (Coords, Coords) Source #

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

focusedRobot :: GameState -> Maybe Robot Source #

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

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.

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.

sleepUntil :: Has (State GameState) sig m => RID -> Integer -> 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 #

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.