License | BSD-3-Clause |
---|---|
Safe Haskell | None |
Language | Haskell2010 |
Swarm.Game.Step.Util
Description
Utilities for implementing robot commands.
Synopsis
- deriveHeading :: forall (sig :: (Type -> Type) -> Type -> Type) m. HasRobotStepState sig m => Direction -> m Heading
- lookInDirection :: forall (sig :: (Type -> Type) -> Type -> Type) m. HasRobotStepState sig m => Direction -> m (Cosmic Location, Maybe Entity)
- adaptGameState :: forall (sig :: (Type -> Type) -> Type -> Type) m b. Has (State GameState) sig m => State GameState b -> m b
- updateEntityAt :: forall (sig :: (Type -> Type) -> Type -> Type) m. (Has (State Robot) sig m, Has (State GameState) sig m) => Cosmic Location -> (Maybe Entity -> Maybe Entity) -> m ()
- isPrivilegedBot :: forall (sig :: (Type -> Type) -> Type -> Type) m. (Has (State GameState) sig m, Has (State Robot) sig m) => m Bool
- hasCapability :: forall (sig :: (Type -> Type) -> Type -> Type) m. (Has (State Robot) sig m, Has (State GameState) sig m) => Capability -> m Bool
- hasCapabilityFor :: forall (sig :: (Type -> Type) -> Type -> Type) m. (Has (State Robot) sig m, Has (State GameState) sig m, Has (Throw Exn) sig m) => Capability -> Term -> m ()
- holdsOrFail' :: forall (sig :: (Type -> Type) -> Type -> Type) m. Has (Throw Exn) sig m => Const -> Bool -> [Text] -> m ()
- isJustOrFail' :: forall (sig :: (Type -> Type) -> Type -> Type) m a. Has (Throw Exn) sig m => Const -> Maybe a -> [Text] -> m a
- cmdExn :: Const -> [Text] -> Exn
- flagRedraw :: forall (sig :: (Type -> Type) -> Type -> Type) m. Has (State GameState) sig m => m ()
- uniform :: forall (sig :: (Type -> Type) -> Type -> Type) m a. (Has (State GameState) sig m, UniformRange a) => (a, a) -> m a
- weightedChoice :: forall (sig :: (Type -> Type) -> Type -> Type) m a. Has (State GameState) sig m => (a -> Integer) -> [a] -> m (Maybe a)
- randomName :: forall (sig :: (Type -> Type) -> Type -> Type) m. Has (State GameState) sig m => m Text
- checkMoveFailureUnprivileged :: forall (sig :: (Type -> Type) -> Type -> Type) m. HasRobotStepState sig m => Cosmic Location -> m (Maybe MoveFailureMode)
- checkMoveFailure :: forall (sig :: (Type -> Type) -> Type -> Type) m. HasRobotStepState sig m => Cosmic Location -> m (Maybe MoveFailureMode)
Documentation
deriveHeading :: forall (sig :: (Type -> Type) -> Type -> Type) m. HasRobotStepState sig m => Direction -> m Heading Source #
lookInDirection :: forall (sig :: (Type -> Type) -> Type -> Type) m. HasRobotStepState sig m => Direction -> m (Cosmic Location, Maybe Entity) Source #
adaptGameState :: forall (sig :: (Type -> Type) -> Type -> Type) m b. Has (State GameState) sig m => State GameState b -> m b Source #
updateEntityAt :: forall (sig :: (Type -> Type) -> Type -> Type) m. (Has (State Robot) sig m, Has (State GameState) sig m) => Cosmic Location -> (Maybe Entity -> Maybe Entity) -> m () Source #
Modify the entity (if any) at a given location.
Capabilities
isPrivilegedBot :: forall (sig :: (Type -> Type) -> Type -> Type) m. (Has (State GameState) sig m, Has (State Robot) sig m) => m Bool Source #
Exempts the robot from various command constraints when it is either a system robot or playing in creative mode
hasCapability :: forall (sig :: (Type -> Type) -> Type -> Type) m. (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 :: forall (sig :: (Type -> Type) -> Type -> Type) m. (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.
Exceptions
holdsOrFail' :: forall (sig :: (Type -> Type) -> Type -> Type) m. Has (Throw Exn) sig m => Const -> Bool -> [Text] -> m () Source #
isJustOrFail' :: forall (sig :: (Type -> Type) -> Type -> Type) m a. Has (Throw Exn) sig m => Const -> Maybe a -> [Text] -> m a Source #
Some utility functions
flagRedraw :: forall (sig :: (Type -> Type) -> Type -> Type) m. Has (State GameState) sig m => m () Source #
Set a flag telling the UI that the world needs to be redrawn.
Randomness
uniform :: forall (sig :: (Type -> Type) -> Type -> Type) m a. (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 :: forall (sig :: (Type -> Type) -> Type -> Type) m a. 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 :: forall (sig :: (Type -> Type) -> Type -> Type) m. Has (State GameState) sig m => m Text Source #
Generate a random robot name in the form adjective_name
.
Moving
checkMoveFailureUnprivileged :: forall (sig :: (Type -> Type) -> Type -> Type) m. HasRobotStepState sig m => Cosmic Location -> m (Maybe MoveFailureMode) Source #
Raw check whether moving to the given location causes any kind of
failure, with no special checks for system robots (see also
checkMoveFailure
).
checkMoveFailure :: forall (sig :: (Type -> Type) -> Type -> Type) m. HasRobotStepState sig m => Cosmic Location -> m (Maybe MoveFailureMode) Source #
Check whether moving to the given location causes any kind of failure. Note that system robots have unrestricted movement and never fail, but non-system robots have restricted movement even in creative mode.