swarm-0.1.0.0: 2D resource gathering game with programmable robots
CopyrightBrent Yorgey
LicenseBSD-3-Clause
Maintainerbyorgey@gmail.com
Safe HaskellSafe-Inferred
LanguageHaskell2010

Swarm.Game.Step

Description

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

Synopsis

Documentation

gameTick :: (Has (State GameState) sig m, Has (Lift IO) sig m) => m () Source #

The main function to do one game tick. The only reason we need IO is so that robots can run programs loaded from files, via the Run command; but eventually I want to get rid of that command and have a library of modules that you can create, edit, and run all from within the UI (the library could also be loaded from a file when the whole program starts up).

evalPT :: (Has (Lift IO) sig m, Has (Throw Exn) sig m, Has (State GameState) sig m) => ProcessedTerm -> m Value Source #

getNow :: Has (Lift IO) sig m => m TimeSpec 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 (Lift IO) sig m, Has (Throw Exn) sig m, Has (State GameState) sig m) => CESK -> m Value Source #

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

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

Set a flag telling the UI that the world needs to be redrawn.

zoomWorld :: Has (State GameState) sig m => StateC (World Int Entity) Identity b -> m b Source #

Perform an action requiring a World state component in a larger context with a GameState.

entityAt :: Has (State GameState) sig m => V2 Int64 -> m (Maybe Entity) Source #

Get the entity (if any) at a given location.

updateEntityAt :: Has (State GameState) sig m => V2 Int64 -> (Maybe Entity -> Maybe Entity) -> m () Source #

Modify the entity (if any) at a given location.

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

Get the robot with a given ID.

robotWithName :: Has (State GameState) sig m => Text -> m (Maybe Robot) Source #

Get the robot with a given name.

uniform :: (Has (State GameState) sig m, UniformRange a) => (a, a) -> m a Source #

Generate a uniformly random number using the random generator in the game state.

weightedChoice :: Has (State GameState) sig m => (a -> Integer) -> [a] -> m (Maybe a) Source #

Given a weighting function and a list of values, choose one of the values randomly (using the random generator in the game state), with the probability of each being proportional to its weight. Return Nothing if the list is empty.

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

Generate a random robot name in the form adjective_name.

createLogEntry :: (Has (State GameState) sig m, Has (State Robot) sig m) => LogSource -> Text -> m LogEntry Source #

Create a log entry given current robot and game time in ticks noting whether it has been said.

This is the more generic version used both for (recorded) said messages and normal logs.

traceLog :: (Has (State GameState) sig m, Has (State Robot) sig m) => LogSource -> Text -> m LogEntry Source #

Print some text via the robot's log.

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.

constCapsFor :: Const -> Robot -> Maybe Capability Source #

Capabilities needed for a specific robot to evaluate or execute a constant. Right now, the only difference is whether the robot is heavy or not when executing the Move command, but there might be other exceptions added in the future.

ensureCanExecute :: (Has (State Robot) sig m, Has (State GameState) sig m, Has (Throw Exn) sig m) => Const -> m () Source #

Ensure that a robot is capable of executing a certain constant (either because it has a device which gives it that capability, or it is a system robot, or we are in creative mode).

hasCapability :: (Has (State Robot) sig m, Has (State GameState) sig m) => Capability -> m Bool Source #

Test whether the current robot has a given capability (either because it has a device which gives it that capability, or it is a system robot, or we are in creative mode).

hasCapabilityFor :: (Has (State Robot) sig m, Has (State GameState) sig m, Has (Throw Exn) sig m) => Capability -> Term -> m () Source #

Ensure that either a robot has a given capability, OR we are in creative mode.

cmdExn :: Const -> [Text] -> Exn Source #

Create an exception about a command failing.

raise :: Has (Throw Exn) sig m => Const -> [Text] -> m a Source #

Raise an exception about a command failing with a formatted error message.

withExceptions :: Monad m => Store -> Cont -> ThrowC Exn m CESK -> m CESK Source #

Run a subcomputation that might throw an exception in a context where we are returning a CESK machine; any exception will be turned into an Up state.

tickRobot :: (Has (State GameState) sig m, Has (Lift IO) 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 :: (Has (State GameState) sig m, Has (Lift IO) 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 :: (Has (State GameState) sig m, Has (Lift IO) sig m) => Robot -> m Robot Source #

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

stepCESK :: (Has (State GameState) sig m, Has (State Robot) sig m, Has (Lift IO) 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.

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

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

seedProgram :: Integer -> Integer -> Text -> ProcessedTerm Source #

A system program for a "seed robot", to regrow a growable entity after it is harvested.

addSeedBot :: Has (State GameState) sig m => Entity -> (Integer, Integer) -> V2 Int64 -> TimeSpec -> m () Source #

Construct a "seed robot" from entity, time range and position, and add it to the world. It has low priority and will be covered by placed entities.

type HasRobotStepState sig m = (Has (State GameState) sig m, Has (State Robot) sig m, Has (Throw Exn) sig m) Source #

All functions that are used for robot step can access GameState and the current Robot.

They can also throw exception of our custom type, which is handled elsewhere. Because of that the constraint is only Throw, but not Catch/Error.

execConst :: (HasRobotStepState sig m, Has (Lift IO) sig m) => Const -> [Value] -> Store -> Cont -> m CESK Source #

Interpret the execution (or evaluation) of a constant application to some values.

data RobotFailure Source #

How to handle failure, for example when moving to blocked location

Constructors

ThrowExn 
Destroy 
IgnoreFail 

data MoveFailure Source #

How to handle failure when moving/teleporting to a location.

data GrabbingCmd Source #

Constructors

Grab' 
Harvest' 
Swap' 

Instances

Instances details
Show GrabbingCmd Source # 
Instance details

Defined in Swarm.Game.Step

Eq GrabbingCmd Source # 
Instance details

Defined in Swarm.Game.Step

provisionChild :: HasRobotStepState sig m => RID -> Inventory -> Inventory -> m () Source #

Give some entities from a parent robot (the robot represented by the ambient State Robot effect) to a child robot (represented by the given RID) as part of a Build or Reprogram command. The first Inventory is devices to be installed, and the second is entities to be transferred.

In classic mode, the entities will be transferred (that is, removed from the parent robot's inventory); in creative mode, the entities will be copied/created, that is, no entities will be removed from the parent robot.

updateRobotLocation :: HasRobotStepState sig m => V2 Int64 -> V2 Int64 -> m () Source #

Update the location of a robot, and simultaneously update the robotsByLocation map, so we can always look up robots by location. This should be the only way to update the location of a robot.

onTarget :: HasRobotStepState sig m => RID -> (forall sig' m'. HasRobotStepState sig' m' => m' ()) -> m () Source #

Execute a stateful action on a target robot --- whether the current one or another.

evalCmp :: Has (Throw Exn) sig m => Const -> Value -> Value -> m Bool Source #

Evaluate the application of a comparison operator. Returns Nothing if the application does not make sense.

compareValues :: Has (Throw Exn) sig m => Value -> Value -> m Ordering Source #

Compare two values, returning an Ordering if they can be compared, or Nothing if they cannot.

incompatCmp :: Has (Throw Exn) sig m => Value -> Value -> m a Source #

Values with different types were compared; this should not be possible since the type system should catch it.

incomparable :: Has (Throw Exn) sig m => Value -> Value -> m a Source #

Values were compared of a type which cannot be compared (e.g. functions, etc.).

evalArith :: Has (Throw Exn) sig m => Const -> Integer -> Integer -> m Integer Source #

Evaluate the application of an arithmetic operator, returning an exception in the case of a failing operation, or in case we incorrectly use it on a bad Const in the library.

safeDiv :: Has (Throw Exn) sig m => Integer -> Integer -> m Integer Source #

Perform an integer division, but return Nothing for division by zero.

safeExp :: Has (Throw Exn) sig m => Integer -> Integer -> m Integer Source #

Perform exponentiation, but return Nothing if the power is negative.

updateDiscoveredEntities :: HasRobotStepState sig m => Entity -> m () Source #

Update the global list of discovered entities, and check for new recipes.

updateAvailableRecipes :: Has (State GameState) sig m => (Inventory, Inventory) -> Entity -> m () Source #

Update the availableRecipes list. This implementation is not efficient: * Every time we discover a new entity, we iterate through the entire list of recipes to see which ones we can make. Trying to do something more clever seems like it would definitely be a case of premature optimization. One doesn't discover new entities all that often. * For each usable recipe, we do a linear search through the list of known recipes to see if we already know it. This is a little more troubling, since it's quadratic in the number of recipes. But it probably doesn't really make that much difference until we get up to thousands of recipes.