Skip to content

Commit

Permalink
fix haddock quotes
Browse files Browse the repository at this point in the history
  • Loading branch information
kostmo committed Jul 14, 2023
1 parent 7a0b587 commit 801f75d
Show file tree
Hide file tree
Showing 10 changed files with 27 additions and 28 deletions.
1 change: 0 additions & 1 deletion src/Swarm/Game/Scenario.hs
Original file line number Diff line number Diff line change
Expand Up @@ -134,7 +134,6 @@ instance FromJSONE EntityMap Scenario where
let rsMap = buildRobotMap rs

rootLevelSharedStructures <- localE (,rsMap) $ v ..:? "structures" ..!= []
-- fail $ show rootLevelSharedStructures

allWorlds <- localE (\x -> (rootLevelSharedStructures :: Structure.InheritedStructureDefs, (x, rsMap))) $ do
rootWorld <- v ..: "world"
Expand Down
2 changes: 1 addition & 1 deletion src/Swarm/Game/Scenario/Topography/Cell.hs
Original file line number Diff line number Diff line change
Expand Up @@ -97,7 +97,7 @@ instance FromJSONE (EntityMap, RobotMap) (AugmentedCell Entity) where
AugmentedCell
<$> liftE (v .:? "waypoint")
<*> v
..: "cell"
..: "cell"

------------------------------------------------------------
-- World editor
Expand Down
6 changes: 3 additions & 3 deletions src/Swarm/Game/Scenario/Topography/Navigation/Portal.hs
Original file line number Diff line number Diff line change
Expand Up @@ -87,7 +87,7 @@ failWaypointLookup (WaypointName rawName) lookupResult = case lookupResult of
-- The following constraints must be enforced:
-- * portals based on plural waypoint multiplicity can have multiple entrances but only a single exit
-- * no two portals share the same entrance location
-- * waypoint uniqueness within a subworld when the "unique" flag is specified
-- * waypoint uniqueness within a subworld when the 'unique' flag is specified
--
-- == Data flow:
--
Expand Down Expand Up @@ -184,7 +184,7 @@ validatePortals (Navigation wpUniverse partialPortals) = do
M.lookup wpWrapper subworldWaypoints

-- | A portal can be marked as \"consistent\", meaning that it represents
-- a conventional physical passage rather than a "magical" teleportation.
-- a conventional physical passage rather than a \"magical\" teleportation.
--
-- If there exists more than one \"consistent\" portal between the same
-- two subworlds, then the portal locations must be spatially consistent
Expand All @@ -196,7 +196,7 @@ validatePortals (Navigation wpUniverse partialPortals) = do
-- * The coordinates of all \"consistent\" portal locations in Subworld A
-- are subtracted from the corresponding coordinates in Subworld B. It
-- does not matter which are exits vs. entrances.
-- * The resulting "vector" from every pair must be equal.
-- * The resulting \"vector\" from every pair must be equal.
ensureSpatialConsistency ::
MonadFail m =>
-- Navigation (M.Map SubworldName) WaypointName ->
Expand Down
2 changes: 1 addition & 1 deletion src/Swarm/Game/Scenario/Topography/Structure.hs
Original file line number Diff line number Diff line change
Expand Up @@ -38,7 +38,7 @@ instance FromJSONE (EntityMap, RobotMap) (NamedStructure (Maybe (PCell Entity)))
NamedStructure
<$> liftE (v .: "name")
<*> v
..: "structure"
..: "structure"

data PStructure c = Structure
{ area :: [[c]]
Expand Down
18 changes: 9 additions & 9 deletions src/Swarm/Game/State.hs
Original file line number Diff line number Diff line change
Expand Up @@ -488,7 +488,7 @@ robotsAtLocation loc gs =
. view robotsByLocation
$ gs

-- | Get a list of all the robots that are "watching" by location.
-- | Get a list of all the robots that are \"watching\" by location.
robotsWatching :: Lens' GameState (Map (Cosmo Location) (S.Set RID))

-- | Get all the robots within a given Manhattan distance from a
Expand Down Expand Up @@ -570,13 +570,13 @@ currentScenarioPath :: Lens' GameState (Maybe FilePath)
-- robots know what they are without having to scan them.
knownEntities :: Lens' GameState [Text]

-- | Includes a "Map" of named locations and an
-- | Includes a 'Map' of named locations and an
-- "Edge list" (graph) that maps portal entrances to exits
worldNavigation :: Lens' GameState (Navigation (M.Map SubworldName) Location)

-- | 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
-- 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.
multiWorld :: Lens' GameState (W.MultiWorld Int Entity)

Expand All @@ -585,8 +585,8 @@ worldScrollable :: Lens' GameState Bool

-- | 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".
-- 'viewCenterRule'. To modify the view center, either set the
-- 'viewCenterRule', or use 'modifyViewCenter'.
viewCenter :: Getter GameState (Cosmo Location)
viewCenter = to _viewCenter

Expand Down Expand Up @@ -693,15 +693,15 @@ messageNotifications = to getNotif
messageIsRecent :: GameState -> LogEntry -> Bool
messageIsRecent gs e = addTicks 1 (e ^. leTime) >= gs ^. ticks

-- | If the log location is "Nothing", consider it omnipresent.
-- | If the log location is 'Nothing', consider it omnipresent.
messageIsFromNearby :: Cosmo Location -> LogEntry -> Bool
messageIsFromNearby l e = maybe True f (e ^. leLocation)
where
f logLoc = maybe False (<= hearingDistance) $ cosmoMeasure manhattan l logLoc

-- | 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
-- is 'Maybe' because the rule may refer to a robot which does not
-- exist.
applyViewCenterRule :: ViewCenterRule -> IntMap Robot -> Maybe (Cosmo Location)
applyViewCenterRule (VCLocation l) _ = Just l
Expand Down Expand Up @@ -972,7 +972,7 @@ deleteRobot rn = do
removeRobotFromLocationMap (robot ^. robotLocation) rn

-- | Makes sure empty sets don't hang around in the
-- robotsByLocation map. We don't want a key with an
-- 'robotsByLocation' map. We don't want a key with an
-- empty set at every location any robot has ever
-- visited!
removeRobotFromLocationMap ::
Expand Down
4 changes: 2 additions & 2 deletions src/Swarm/Game/Step.hs
Original file line number Diff line number Diff line change
Expand Up @@ -1619,7 +1619,7 @@ execConst c vs s k = do
emitMessage m
let manhattanToLog :: Cosmo Location -> Maybe (Cosmo Location) -> Maybe Int32
-- Measures the Manhattan distance between a robot and a (Maybe) log location.
-- If log location is Nothing, it is "omnipresent" and therefore distance is zero.
-- If log location is Nothing, it is \"omnipresent\" and therefore distance is zero.
manhattanToLog robLoc maybeLogLoc = case maybeLogLoc of
Just logLoc -> cosmoMeasure manhattan robLoc logLoc
Nothing -> Just 0
Expand All @@ -1630,7 +1630,7 @@ execConst c vs s k = do
| (cmpManhattan `on` (manhattanToLog rl . view leLocation)) e m -> es |> m
| otherwise -> es |> e
where
-- Returns True if M1 is not smaller than M2. "Nothing" is treated as infinite.
-- Returns True if M1 is not smaller than M2. 'Nothing' is treated as infinite.
-- TODO: Should probably define a new, parameterized datatype isomorphic to
-- Maybe that makes this convention explicit.
cmpManhattan maybeM1 maybeM2 = case maybeM1 of
Expand Down
2 changes: 1 addition & 1 deletion src/Swarm/Game/Universe.hs
Original file line number Diff line number Diff line change
Expand Up @@ -58,7 +58,7 @@ instance (FromJSON a) => FromJSON (Cosmo a) where
defaultCosmoLocation :: Cosmo Location
defaultCosmoLocation = Cosmo defaultRootSubworldName origin

-- | Returns "Nothing" if not within the same subworld.
-- | Returns 'Nothing' if not within the same subworld.
-- TODO: Define a new datatype isomorphic to Maybe for this.
cosmoMeasure :: (a -> a -> b) -> Cosmo a -> Cosmo a -> Maybe b
cosmoMeasure f a b = do
Expand Down
16 changes: 8 additions & 8 deletions src/Swarm/Game/World.hs
Original file line number Diff line number Diff line change
Expand Up @@ -32,7 +32,7 @@ module Swarm.Game.World (
-- ** World functions
newWorld,
emptyWorld,
lookupCosmosTerrain,
lookupCosmoTerrain,
lookupTerrain,
lookupCosmoEntity,
lookupEntity,
Expand Down Expand Up @@ -222,12 +222,12 @@ newWorld f = World f M.empty M.empty
emptyWorld :: t -> World t e
emptyWorld t = newWorld (WF $ const (t, Nothing))

lookupCosmosTerrain ::
lookupCosmoTerrain ::
IArray U.UArray Int =>
Cosmo Coords ->
MultiWorld Int e ->
TerrainType
lookupCosmosTerrain (Cosmo subworldName i) multiWorld =
lookupCosmoTerrain (Cosmo subworldName i) multiWorld =
maybe BlankT (toEnum . lookupTerrain i) $ M.lookup subworldName multiWorld

-- | Look up the terrain value at certain coordinates: try looking it
Expand All @@ -241,7 +241,7 @@ lookupTerrain i (World f t _) =
((U.! tileOffset i) . fst <$> M.lookup (tileCoords i) t)
? fst (runWF f i)

-- | A stateful variant of "lookupTerrain", which first loads the tile
-- | A stateful variant of 'lookupTerrain', which first loads the tile
-- containing the given coordinates if it is not already loaded,
-- then looks up the terrain value.
lookupTerrainM ::
Expand All @@ -260,17 +260,17 @@ lookupCosmoEntity (Cosmo subworldName i) multiWorld =
-- | Look up the entity at certain coordinates: first, see if it is in
-- the map of locations with changed entities; then try looking it
-- up in the tile cache first; and finally fall back to running the
-- "WorldFun".
-- 'WorldFun'.
--
-- This function does /not/ ensure that the tile containing the
-- given coordinates is loaded. For that, see "lookupEntityM".
-- given coordinates is loaded. For that, see 'lookupEntityM'.
lookupEntity :: Coords -> World t e -> Maybe e
lookupEntity i (World f t m) =
M.lookup i m
? ((A.! tileOffset i) . snd <$> M.lookup (tileCoords i) t)
? snd (runWF f i)

-- | A stateful variant of "lookupEntity", which first loads the tile
-- | A stateful variant of 'lookupEntity', which first loads the tile
-- containing the given coordinates if it is not already loaded,
-- then looks up the terrain value.
lookupEntityM ::
Expand Down Expand Up @@ -298,7 +298,7 @@ update i g w@(World f t m) =
entityBefore = lookupEntity i w
entityAfter = g entityBefore

-- | A stateful variant of "update", which also ensures the tile
-- | A stateful variant of 'update', which also ensures the tile
-- containing the given coordinates is loaded.
updateM ::
forall t sig m.
Expand Down
2 changes: 1 addition & 1 deletion src/Swarm/TUI/Editor/Util.hs
Original file line number Diff line number Diff line change
Expand Up @@ -58,7 +58,7 @@ getContentAt editor w coords =

entityWithOverride = (Ref <$> underlyingCellEntity) <|> maybeEntityOverride
underlyingCellEntity = W.lookupCosmoEntity coords w
underlyingCellTerrain = W.lookupCosmosTerrain coords w
underlyingCellTerrain = W.lookupCosmoTerrain coords w

getTerrainAt ::
WorldEditor Name ->
Expand Down
2 changes: 1 addition & 1 deletion src/Swarm/TUI/View/CellDisplay.hs
Original file line number Diff line number Diff line change
Expand Up @@ -80,7 +80,7 @@ displayEntityCell worldEditor g coords =
e
`hasProperty` Known
|| (e ^. entityName)
`elem` (g ^. knownEntities)
`elem` (g ^. knownEntities)
|| case hidingMode g of
HideAllEntities -> False
HideNoEntity -> True
Expand Down

0 comments on commit 801f75d

Please sign in to comment.