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

Swarm.Game.Step

Description

Facilities for stepping the robot CESK machines, i.e. the actual interpreter for the Swarm language.

Note on the IO:

The only reason we need IO is so that robots can run programs loaded from files, via the Run command. This could be avoided by using a hypothetical import command instead and parsing the required files at the time of declaration. See https://github.com/swarm-game/swarm/issues/495.

Synopsis

Documentation

gameTick :: HasGameStepState sig m => m Bool Source #

The main function to do one game tick.

Note that the game may be in RobotStep mode and not finish the tick. Use the return value to check whether a full tick happened.

finishGameTick :: HasGameStepState sig m => m () Source #

Finish a game tick in progress and set the game to WorldTick mode afterwards.

Use this function if you need to unpause the game.

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

Insert the robot back to robot map. Will selfdestruct or put the robot to sleep if it has that set.

type HasGameStepState sig m = (Has (State GameState) sig m, Has (Lift IO) sig m, Has Time sig m) Source #

GameState with support for IO and Time effect

runRobotIDs :: HasGameStepState sig m => IntSet -> m () Source #

Run a set of robots - this is used to run robots before/after the focused one.

Note that during the iteration over the supplied robot IDs, it is possible that a robot that may have been present in robotMap at the outset of the iteration to be removed before the iteration comes upon it. This is why we must perform a robotMap lookup at each iteration, rather than looking up elements from robotMap in bulk up front with something like restrictKeys.

Invariants

  • Every tick, every active robot shall have exactly one opportunity to run.
  • The sequence in which robots are chosen to run is by increasing order of RID.

iterateRobots :: HasGameStepState sig m => TickNumber -> (RID -> m ()) -> IntSet -> m () Source #

Runs the given robots in increasing order of RID.

Running a given robot _may_ cause another robot with a higher RID to be inserted into the runnable set.

Note that the behavior we desire is described precisely by a https://en.wikipedia.org/wiki/Monotone_priority_queue.

A priority queue allows O(1) access to the lowest priority item. However, splitting the min item from rest of the queue is still an O(log N) operation, and therefore is not any better than the minView function from IntSet.

Tail-recursive.

singleStep :: HasGameStepState sig m => SingleStep -> RID -> IntSet -> m Bool Source #

This is a helper function to do one robot step or run robots before/after.

data CompletionsWithExceptions Source #

An accumulator for folding over the incomplete objectives to evaluate for their completion

Constructors

CompletionsWithExceptions 

Fields

hypotheticalWinCheck :: (Has (State GameState) sig m, Has Time sig m, Has (Lift IO) sig m) => EntityMap -> GameState -> WinStatus -> ObjectiveCompletion -> m () Source #

Execute the win condition check *hypothetically*: i.e. in a fresh CESK machine, using a copy of the current game state.

The win check is performed only on "active" goals; that is, the goals that are currently unmet and have had all of their prerequisites satisfied. Note that it may be possible, while traversing through the goal list, for one goal to be met earlier in the list that happens to be a prerequisite later in the traversal. This is why: 1) We must not pre-filter the goals to be traversed based on satisfied prerequisites (i.e. we cannot use the "getActiveObjectives" function). 2) The traversal order must be "reverse topological" order, so that prerequisites are evaluated before dependent goals. 3) The iteration needs to be a "fold", so that state is updated after each element.

evalT :: (Has Time sig m, Has (Throw Exn) sig m, Has (State GameState) sig m, Has (Lift IO) sig m) => TSyntax -> m Value Source #

hypotheticalRobot :: CESK -> TimeSpec -> Robot Source #

Create a special robot to check some hypothetical, for example the win condition.

Use ID (-1) so it won't conflict with any robots currently in the robot map.

evaluateCESK :: (Has Time sig m, Has (Throw Exn) sig m, Has (State GameState) sig m, Has (Lift IO) sig m) => CESK -> m Value Source #

runCESK :: (Has Time sig m, Has (Lift IO) sig m, Has (Throw Exn) sig m, Has (State GameState) sig m, Has (State Robot) sig m) => CESK -> m Value Source #

traceLogShow :: (Has (State GameState) sig m, Has (State Robot) sig m, Show a) => a -> m () Source #

Print a showable value via the robot's log.

Useful for debugging.

tickRobot :: HasGameStepState sig m => Robot -> m Robot Source #

Run a robot for one tick, which may consist of up to robotStepsPerTick CESK machine steps and at most one tangible command execution, whichever comes first.

tickRobotRec :: HasGameStepState sig m => Robot -> m Robot Source #

Recursive helper function for tickRobot, which checks if the robot is actively running and still has steps left, and if so runs it for one step, then calls itself recursively to continue stepping the robot.

stepRobot :: HasGameStepState sig m => Robot -> m Robot Source #

Single-step a robot by decrementing its tickStepBudget counter and running its CESK machine for one step.

data SKpair Source #

Constructors

SKpair Store Cont 

processImmediateFrame Source #

Arguments

:: (Has (State GameState) sig m, Has (State Robot) sig m, Has (Lift IO) sig m, Has Time sig m) 
=> Value 
-> SKpair 
-> ErrorC Exn m ()

the unreliable computation

-> m CESK 

Performs some side-effectful computation for an FImmediate Frame. Aborts processing the continuation stack if an error is encountered.

Compare to "withExceptions".

stepCESK :: (Has (State GameState) sig m, Has (State Robot) sig m, Has (Lift IO) sig m, Has Time sig m) => CESK -> m CESK Source #

The main CESK machine workhorse. Given a robot, look at its CESK machine state and figure out a single next step.

runChildProg :: (HasRobotStepState sig m, Has Time sig m, Has (Lift IO) sig m) => Store -> Robot -> Value -> m Value Source #

Execute the given program *hypothetically*: i.e. in a fresh CESK machine, using *copies* of the current store, robot and game state. We discard the state afterwards so any modifications made by prog do not persist. Note we also set the copied robot to be a "system" robot so it is capable of executing any commands; the As command already requires God capability.

evalConst :: (Has (State GameState) sig m, Has (State Robot) sig m, Has Time sig m, Has (Lift IO) sig m) => Const -> [Value] -> Store -> Cont -> m CESK Source #

Execute a constant, catching any exception thrown and returning it via a CESK machine state.