License | BSD-3-Clause |
---|---|
Safe Haskell | None |
Language | Haskell2010 |
Swarm.Game.Scenario
Description
Scenarios are standalone worlds with specific starting and winning conditions, which can be used both for building interactive tutorials and for standalone puzzles and scenarios.
Synopsis
- data Scenario = Scenario {
- _scenarioMetadata :: ScenarioMetadata
- _scenarioOperation :: ScenarioOperation
- _scenarioLandscape :: ScenarioLandscape
- data ScenarioLandscape = ScenarioLandscape {
- _scenarioSeed :: Maybe Int
- _scenarioAttrs :: [CustomAttr]
- _scenarioTerrainAndEntities :: TerrainEntityMaps
- _scenarioCosmetics :: Map WorldAttr PreservableColor
- _scenarioKnown :: Set EntityName
- _scenarioWorlds :: NonEmpty WorldDescription
- _scenarioNavigation :: Navigation (Map SubworldName) Location
- _scenarioStructures :: StaticStructureInfo RecognizableStructureContent Entity
- _scenarioRobots :: [TRobot]
- data ScenarioMetadata = ScenarioMetadata Int Text (Maybe Text)
- type RecognizableStructureContent = NonEmptyGrid (Maybe Cell)
- staticPlacements :: forall b a f. Functor f => (Map SubworldName [LocatedStructure] -> f (Map SubworldName [LocatedStructure])) -> StaticStructureInfo b a -> f (StaticStructureInfo b a)
- scenarioMetadata :: Lens' Scenario ScenarioMetadata
- scenarioOperation :: Lens' Scenario ScenarioOperation
- scenarioLandscape :: Lens' Scenario ScenarioLandscape
- scenarioVersion :: Lens' ScenarioMetadata Int
- scenarioName :: Lens' ScenarioMetadata Text
- scenarioAuthor :: Lens' ScenarioMetadata (Maybe Text)
- scenarioDescription :: Lens' ScenarioOperation (Document Syntax)
- scenarioCreative :: Lens' ScenarioOperation Bool
- scenarioSeed :: Lens' ScenarioLandscape (Maybe Int)
- scenarioAttrs :: Lens' ScenarioLandscape [CustomAttr]
- scenarioTerrainAndEntities :: Lens' ScenarioLandscape TerrainEntityMaps
- scenarioCosmetics :: Lens' ScenarioLandscape (Map WorldAttr PreservableColor)
- scenarioRecipes :: Lens' ScenarioOperation [Recipe Entity]
- scenarioKnown :: Lens' ScenarioLandscape (Set EntityName)
- scenarioWorlds :: Lens' ScenarioLandscape (NonEmpty WorldDescription)
- scenarioNavigation :: Lens' ScenarioLandscape (Navigation (Map SubworldName) Location)
- scenarioStructures :: Lens' ScenarioLandscape (StaticStructureInfo RecognizableStructureContent Entity)
- scenarioRobots :: Lens' ScenarioLandscape [TRobot]
- scenarioObjectives :: Lens' ScenarioOperation [Objective]
- scenarioSolution :: Lens' ScenarioOperation (Maybe TSyntax)
- scenarioStepsPerTick :: Lens' ScenarioOperation (Maybe Int)
- loadScenario :: forall (sig :: (Type -> Type) -> Type -> Type) m. (Has (Throw SystemFailure) sig m, Has (Lift IO) sig m) => FilePath -> ScenarioInputs -> m (Scenario, FilePath)
- loadScenarioFile :: forall (sig :: (Type -> Type) -> Type -> Type) m. (Has (Throw SystemFailure) sig m, Has (Lift IO) sig m) => ScenarioInputs -> FilePath -> m Scenario
- getScenarioPath :: forall (sig :: (Type -> Type) -> Type -> Type) m. Has (Lift IO) sig m => FilePath -> m (Maybe FilePath)
- loadStandaloneScenario :: forall (sig :: (Type -> Type) -> Type -> Type) m. (Has (Throw SystemFailure) sig m, Has (Lift IO) sig m) => FilePath -> m (Scenario, GameStateInputs)
- data GameStateInputs = GameStateInputs {}
- data ScenarioInputs = ScenarioInputs {}
- arbitrateSeed :: Maybe Seed -> ScenarioLandscape -> IO Seed
Scenario
A Scenario
contains all the information to describe a
scenario.
Constructors
Scenario | |
Fields
|
Instances
FromJSONE ScenarioInputs Scenario Source # | |
Defined in Swarm.Game.Scenario Methods parseJSONE :: Value -> ParserE ScenarioInputs Scenario parseJSONE' :: ScenarioInputs -> Value -> Parser Scenario |
data ScenarioLandscape Source #
All cosmetic and structural content of the scenario.
Constructors
ScenarioLandscape | |
Fields
|
data ScenarioMetadata Source #
Authorship information about scenario not used at play-time
Constructors
ScenarioMetadata Int Text (Maybe Text) |
Instances
type RecognizableStructureContent = NonEmptyGrid (Maybe Cell) Source #
staticPlacements :: forall b a f. Functor f => (Map SubworldName [LocatedStructure] -> f (Map SubworldName [LocatedStructure])) -> StaticStructureInfo b a -> f (StaticStructureInfo b a) #
Fields
scenarioMetadata :: Lens' Scenario ScenarioMetadata Source #
Authorship information about scenario not used at play-time
scenarioOperation :: Lens' Scenario ScenarioOperation Source #
Non-structural gameplay content of the scenario; how it is to be played.
scenarioLandscape :: Lens' Scenario ScenarioLandscape Source #
All cosmetic and structural content of the scenario.
scenarioVersion :: Lens' ScenarioMetadata Int Source #
The version number of the scenario schema. Currently, this should always be 1, but it is ignored. In the future, this may be used to convert older formats to newer ones, or simply to print a nice error message when we can't read an older format.
scenarioName :: Lens' ScenarioMetadata Text Source #
The name of the scenario.
scenarioAuthor :: Lens' ScenarioMetadata (Maybe Text) Source #
The author of the scenario.
scenarioDescription :: Lens' ScenarioOperation (Document Syntax) Source #
A high-level description of the scenario, shown e.g. in the menu.
scenarioCreative :: Lens' ScenarioOperation Bool Source #
Whether the scenario should start in creative mode.
scenarioSeed :: Lens' ScenarioLandscape (Maybe Int) Source #
The seed used for the random number generator. If Nothing
, use
a random seed / prompt the user for the seed.
scenarioAttrs :: Lens' ScenarioLandscape [CustomAttr] Source #
Custom attributes defined in the scenario.
scenarioTerrainAndEntities :: Lens' ScenarioLandscape TerrainEntityMaps Source #
Any custom terrain and entities used for this scenario, combined with the default system terrain and entities.
scenarioCosmetics :: Lens' ScenarioLandscape (Map WorldAttr PreservableColor) Source #
High-fidelity color map for entities
scenarioRecipes :: Lens' ScenarioOperation [Recipe Entity] Source #
Any custom recipes used in this scenario.
scenarioKnown :: Lens' ScenarioLandscape (Set EntityName) Source #
List of entities that should be considered "known", so robots do not have to scan them.
scenarioWorlds :: Lens' ScenarioLandscape (NonEmpty WorldDescription) Source #
The subworlds of the scenario. The "root" subworld shall always be at the head of the list, by construction.
scenarioNavigation :: Lens' ScenarioLandscape (Navigation (Map SubworldName) Location) Source #
Waypoints and inter-world portals
scenarioStructures :: Lens' ScenarioLandscape (StaticStructureInfo RecognizableStructureContent Entity) Source #
Information required for structure recognition
scenarioRobots :: Lens' ScenarioLandscape [TRobot] Source #
The starting robots for the scenario. Note this should include the base.
scenarioObjectives :: Lens' ScenarioOperation [Objective] Source #
A sequence of objectives for the scenario (if any).
scenarioSolution :: Lens' ScenarioOperation (Maybe TSyntax) Source #
An optional solution of the scenario, expressed as a
program of type cmd a
. This is useful for automated
testing of the win condition.
scenarioStepsPerTick :: Lens' ScenarioOperation (Maybe Int) Source #
Optionally, specify the maximum number of steps each robot may take during a single tick.
Loading from disk
loadScenario :: forall (sig :: (Type -> Type) -> Type -> Type) m. (Has (Throw SystemFailure) sig m, Has (Lift IO) sig m) => FilePath -> ScenarioInputs -> m (Scenario, FilePath) Source #
Load a scenario with a given name from disk, given an entity map to use. This function is used if a specific scenario is requested on the command line.
loadScenarioFile :: forall (sig :: (Type -> Type) -> Type -> Type) m. (Has (Throw SystemFailure) sig m, Has (Lift IO) sig m) => ScenarioInputs -> FilePath -> m Scenario Source #
Load a scenario from a file.
getScenarioPath :: forall (sig :: (Type -> Type) -> Type -> Type) m. Has (Lift IO) sig m => FilePath -> m (Maybe FilePath) Source #
loadStandaloneScenario :: forall (sig :: (Type -> Type) -> Type -> Type) m. (Has (Throw SystemFailure) sig m, Has (Lift IO) sig m) => FilePath -> m (Scenario, GameStateInputs) Source #
Load a single scenario from disk, first loading needed entity + recipe data. This function should only be called in the case of "peripheral" tools that need to load a scenario (for example, documentation generation, scenario world rendering, etc.), not as part of the normal game code path.
data GameStateInputs Source #
Constructors
GameStateInputs | |
Fields
|
data ScenarioInputs Source #
Constructors
ScenarioInputs | |
Fields
|
Instances
FromJSONE ScenarioInputs Scenario Source # | |
Defined in Swarm.Game.Scenario Methods parseJSONE :: Value -> ParserE ScenarioInputs Scenario parseJSONE' :: ScenarioInputs -> Value -> Parser Scenario |
Utilities
arbitrateSeed :: Maybe Seed -> ScenarioLandscape -> IO Seed Source #
Decide on a seed. In order of preference, we will use: 1. seed value provided by the user 2. seed value specified in the scenario description 3. randomly chosen seed value