Skip to content

Commit

Permalink
update behavior and docs for edge cases
Browse files Browse the repository at this point in the history
  • Loading branch information
kostmo committed Sep 24, 2023
1 parent 675b927 commit 2c3c14f
Show file tree
Hide file tree
Showing 3 changed files with 33 additions and 28 deletions.
38 changes: 23 additions & 15 deletions src/Swarm/Game/Scenario/Topography/Navigation/Util.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,30 +5,38 @@ module Swarm.Game.Scenario.Topography.Navigation.Util where
import Control.Lens (view)
import Data.Function (on)
import Data.Int (Int32)
import Linear (V2, zero)
import Linear (V2)
import Swarm.Game.Location
import Swarm.Game.Robot
import Swarm.Game.Universe (Cosmic, planar)
import Swarm.Language.Direction

-- | Given a vector @(x, y)@
-- where:
-- |
-- Computes the relative offset vector between a 'Robot' and a 'Location'
-- (presumed to be in the same subworld, though the contrary will
-- not result in failure), then re-interpret that vector based on the
-- 'Robot'\'s current orientation.
--
-- If the robot is not oriented in a cardinal direction, returns 'Nothing'.
--
-- = Re-orientation semantics
--
-- Given a displacement vector @(x, y)@ where:
--
-- * positive x-coordinate represents @east@
-- * negative x-coordinate represents @west@
-- * positive y-coordinate represents @north@
-- * negative y-coordinate represents @south@
-- * positive @x@-coordinate represents @east@
-- * negative @x@-coordinate represents @west@
-- * positive @y@-coordinate represents @north@
-- * negative @y@-coordinate represents @south@
--
-- re-interpret as relative to a given
-- orientation, where:
-- the re-interpreted vector @(x', y')@ becomes:
--
-- * positive x-coordinate represents @right@
-- * negative x-coordinate represents @left@
-- * positive y-coordinate represents @forward@
-- * negative y-coordinate represents @back@
orientationBasedRelativePosition :: Robot -> Cosmic Location -> V2 Int32
-- * positive @x'@-coordinate represents @right@
-- * negative @x'@-coordinate represents @left@
-- * positive @y'@-coordinate represents @forward@
-- * negative @y'@-coordinate represents @back@
orientationBasedRelativePosition :: Robot -> Cosmic Location -> Maybe (V2 Int32)
orientationBasedRelativePosition selfRobot otherLocation =
maybe zero (`applyTurn` relativeCoords) maybeSelfDirRelativeToNorth
(`applyTurn` relativeCoords) <$> maybeSelfDirRelativeToNorth
where
maybeSelfDirection = view robotOrientation selfRobot >>= toAbsDirection
maybeSelfDirRelativeToNorth = DRelative . DPlanar . relativeTo DNorth <$> maybeSelfDirection
Expand Down
21 changes: 9 additions & 12 deletions src/Swarm/Game/Step.hs
Original file line number Diff line number Diff line change
Expand Up @@ -1209,18 +1209,15 @@ execConst c vs s k = do
maybeOtherRobot <- robotWithID otherID
selfRobot <- get
return $ Out (asValue $ displacementVector selfRobot maybeOtherRobot) s k
where
displacementVector :: Robot -> Maybe Robot -> Maybe (V2 Int32)
displacementVector selfRobot maybeOtherRobot = do
otherRobot <- maybeOtherRobot

let dist = (cosmoMeasure euclidean `on` view robotLocation) selfRobot otherRobot
(_minRange, maxRange) = getRadioRange (Just selfRobot) (Just otherRobot)

d <- getFiniteDistance dist
guard $ d <= maxRange
return $ orientationBasedRelativePosition selfRobot $ view robotLocation otherRobot

where
displacementVector :: Robot -> Maybe Robot -> Maybe (V2 Int32)
displacementVector selfRobot maybeOtherRobot = do
otherRobot <- maybeOtherRobot
let dist = (cosmoMeasure euclidean `on` view robotLocation) selfRobot otherRobot
(_minRange, maxRange) = getRadioRange (Just selfRobot) (Just otherRobot)
d <- getFiniteDistance dist
guard $ d <= maxRange
orientationBasedRelativePosition selfRobot $ view robotLocation otherRobot
_ -> badConst
Give -> case vs of
[VRobot otherID, VText itemName] -> do
Expand Down
2 changes: 1 addition & 1 deletion src/Swarm/Language/Syntax.hs
Original file line number Diff line number Diff line change
Expand Up @@ -564,7 +564,7 @@ constInfo c = case c of
["The current location has to be empty for this to work."]
Ping ->
command 1 short . doc "Obtain the relative location of another robot." $
[ "The other robot must be within transmission range, accounting for antennas installed on either end."
[ "The other robot must be within transmission range, accounting for antennas installed on either end, and the invoking robot must be oriented in a cardinal direction."
, "The location (x, y) is given relative to one's current orientation:"
, "Positive x value is to the right, negative left. Likewise, positive y value is forward, negative back."
]
Expand Down

0 comments on commit 2c3c14f

Please sign in to comment.