| License | BSD-3-Clause |
|---|---|
| Safe Haskell | Safe-Inferred |
| Language | Haskell2010 |
Swarm.Game.Scenario.Topography.Navigation.Portal
Description
Type definitions and validation logic for portals.
Portals can be inter-world or intra-world. It is legal for a portal exit to be on the same cell as its entrance.
By default, passage through a portal preserves the orientation of the robot, but an extra portal parameter can specify that the robot should be re-oriented.
Synopsis
- type WaypointMap = Map WaypointName (NonEmpty Location)
- data AnnotatedDestination a = AnnotatedDestination {}
- data Navigation additionalDimension portalExitLoc = Navigation {
- waypoints :: additionalDimension WaypointMap
- portals :: Map (Cosmic Location) (AnnotatedDestination portalExitLoc)
- data PortalExit = PortalExit {}
- data Portal = Portal {}
- failUponDuplication :: (MonadFail m, Show a, Show b) => Text -> Map a (NonEmpty b) -> m ()
- failWaypointLookup :: MonadFail m => WaypointName -> Maybe a -> m a
- validatePartialNavigation :: (MonadFail m, Traversable t) => SubworldName -> Location -> [Originated Waypoint] -> t Portal -> m (Navigation Identity WaypointName)
- validatePortals :: MonadFail m => Navigation (Map SubworldName) WaypointName -> m (Map (Cosmic Location) (AnnotatedDestination Location))
- ensureSpatialConsistency :: MonadFail m => [(Cosmic Location, AnnotatedDestination Location)] -> m ()
- sequenceSigned :: Functor f => Signed (f a) -> f (Signed a)
Documentation
type WaypointMap = Map WaypointName (NonEmpty Location) Source #
data AnnotatedDestination a Source #
Constructors
| AnnotatedDestination | |
Fields
| |
Instances
| Show a => Show (AnnotatedDestination a) Source # | |
Defined in Swarm.Game.Scenario.Topography.Navigation.Portal Methods showsPrec :: Int -> AnnotatedDestination a -> ShowS # show :: AnnotatedDestination a -> String # showList :: [AnnotatedDestination a] -> ShowS # | |
| Eq a => Eq (AnnotatedDestination a) Source # | |
Defined in Swarm.Game.Scenario.Topography.Navigation.Portal Methods (==) :: AnnotatedDestination a -> AnnotatedDestination a -> Bool # (/=) :: AnnotatedDestination a -> AnnotatedDestination a -> Bool # | |
data Navigation additionalDimension portalExitLoc Source #
Parameterized on waypoint dimensionality (additionalDimension) and
on the portal location specification method (portalExitLoc).
additionalDimension
As a member of the WorldDescription, waypoints are only known within a
a single subworld, so additionalDimension is Identity for the map
of waypoint names to planar locations.
At the Scenario level, in contrast, we have access to all subworlds, so
we nest this map to planar locations in additional mapping layer by subworld.
portalExitLoc
At the subworld parsing level, we only can obtain the planar location for portal entrances, but the exits remain as waypoint names. At the Scenario-parsing level, we finally have access to the waypoints across all subworlds, and can therefore translate the portal exits to concrete planar locations.
Constructors
| Navigation | |
Fields
| |
Instances
data PortalExit Source #
Constructors
| PortalExit | |
Fields
| |
Instances
| FromJSON PortalExit Source # | |
| Generic PortalExit Source # | |
Defined in Swarm.Game.Scenario.Topography.Navigation.Portal Associated Types type Rep PortalExit :: Type -> Type # | |
| Show PortalExit Source # | |
Defined in Swarm.Game.Scenario.Topography.Navigation.Portal Methods showsPrec :: Int -> PortalExit -> ShowS # show :: PortalExit -> String # showList :: [PortalExit] -> ShowS # | |
| Eq PortalExit Source # | |
| type Rep PortalExit Source # | |
Defined in Swarm.Game.Scenario.Topography.Navigation.Portal type Rep PortalExit = D1 ('MetaData "PortalExit" "Swarm.Game.Scenario.Topography.Navigation.Portal" "swarm-0.5.0.0-6qXEbhCmuXA4wRndqqhBu" 'False) (C1 ('MetaCons "PortalExit" 'PrefixI 'True) (S1 ('MetaSel ('Just "exit") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 WaypointName) :*: S1 ('MetaSel ('Just "subworldName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe SubworldName)))) | |
failWaypointLookup :: MonadFail m => WaypointName -> Maybe a -> m a Source #
validatePartialNavigation :: (MonadFail m, Traversable t) => SubworldName -> Location -> [Originated Waypoint] -> t Portal -> m (Navigation Identity WaypointName) Source #
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
uniqueflag is specified
Data flow
Waypoints are defined within a subworld and are namespaced by it.
Optional intra-subworld uniqueness of Waypoints is enforced at WorldDescription
parse time.
Portals are declared within a subworld. The portal entrance must be a waypoint
within this subworld.
They can reference waypoints in other subworlds as exits, but these references
are not validated until the Scenario parse level.
- Since portal entrances are specified at the subworld level, validation that no entrances overlap can also be performed at that level.
- However, enforcement of single-multiplicity on portal exits must be performed
at scenario-parse level, because for a portal exit that references a waypoint in
another subworld, we can't know at the single-
WorldDescriptionlevel whether that waypoint has plural multiplicity.
validatePortals :: MonadFail m => Navigation (Map SubworldName) WaypointName -> m (Map (Cosmic Location) (AnnotatedDestination Location)) Source #
ensureSpatialConsistency :: MonadFail m => [(Cosmic Location, AnnotatedDestination Location)] -> m () Source #
A portal can be marked as "consistent", meaning that it represents 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 between the two worlds. I.e. the space comprising the two subworlds forms a "conservative vector field".
Verifying this is simple: For all of the portals between Subworlds A and B:
- 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.
sequenceSigned :: Functor f => Signed (f a) -> f (Signed a) Source #
An implementation of sequenceA for Signed that does not
require an Applicative instance for the inner Functor.
Discussion
Compare to the Traversable instance of Signed:
instance Traversable Signed where traverse f (Positive x) = Positive $ f x traverse f (Negative x) = Negative $ f x
if we were to substitute id for f:
traverse id (Positive x) = Positive $ id x traverse id (Negative x) = Negative $ id x
our implementation essentially becomes traverse id.
However, we cannot simply write our implementation as traverse id, because
the traverse function has an Applicative constraint, which is superfluous
for our purpose.
Perhaps there is an opportunity to invent a typeclass for datatypes which
consist exclusively of unary (or more ambitiously, non-nullary?) data constructors,
for which a less-constrained sequence function could be automatically derived.
Compare to the Comonad class and its extract function.