swarm-0.6.0.0: 2D resource gathering game with programmable robots
LicenseBSD-3-Clause
Safe HaskellSafe-Inferred
LanguageHaskell2010

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

WorldDescription

data PCell e Source #

A single cell in a world map, which contains a terrain value, and optionally an entity and robot. It is parameterized on the Entity type to facilitate less stateful versions of the Entity type in rendering scenario data.

Constructors

Cell 

Instances

Instances details
ToJSON Cell Source # 
Instance details

Defined in Swarm.Game.Scenario.Topography.Cell

ToJSON CellPaintDisplay Source # 
Instance details

Defined in Swarm.Game.Scenario.Topography.Cell

Show e => Show (PCell e) Source # 
Instance details

Defined in Swarm.Game.Scenario.Topography.Cell

Methods

showsPrec :: Int -> PCell e -> ShowS #

show :: PCell e -> String #

showList :: [PCell e] -> ShowS #

Eq e => Eq (PCell e) Source # 
Instance details

Defined in Swarm.Game.Scenario.Topography.Cell

Methods

(==) :: PCell e -> PCell e -> Bool #

(/=) :: PCell e -> PCell e -> Bool #

FromJSONE (TerrainEntityMaps, RobotMap) Cell Source #

Parse a tuple such as [grass, rock, base] into a PCell. The entity and robot, if present, are immediately looked up and converted into Entity and TRobot values. If they are not found, a parse error results.

Instance details

Defined in Swarm.Game.Scenario.Topography.Cell

type Cell = PCell Entity Source #

A single cell in a world map, which contains a terrain value, and optionally an entity and robot.

data PWorldDescription e Source #

A description of a world parsed from a YAML file. This type is parameterized to accommodate Cells that utilize a less stateful Entity type.

Constructors

WorldDescription 

Fields

type IndexedTRobot = (Int, TRobot) Source #

A robot template paired with its definition's index within the Scenario file

type StructureCells = NamedGrid (Maybe Cell) Source #

Scenario

data Scenario Source #

A Scenario contains all the information to describe a scenario.

Instances

Instances details
Show Scenario Source # 
Instance details

Defined in Swarm.Game.Scenario

FromJSONE ScenarioInputs Scenario Source # 
Instance details

Defined in Swarm.Game.Scenario

data StaticStructureInfo Source #

Constructors

StaticStructureInfo 

Fields

Instances

Instances details
Show StaticStructureInfo Source # 
Instance details

Defined in Swarm.Game.Scenario

data ScenarioMetadata Source #

Authorship information about scenario not used at play-time

Instances

Instances details
ToJSON ScenarioMetadata Source # 
Instance details

Defined in Swarm.Game.Scenario

Generic ScenarioMetadata Source # 
Instance details

Defined in Swarm.Game.Scenario

Associated Types

type Rep ScenarioMetadata :: Type -> Type #

Show ScenarioMetadata Source # 
Instance details

Defined in Swarm.Game.Scenario

type Rep ScenarioMetadata Source # 
Instance details

Defined in Swarm.Game.Scenario

type Rep ScenarioMetadata = D1 ('MetaData "ScenarioMetadata" "Swarm.Game.Scenario" "swarm-0.6.0.0-ERx1HMcRMba59aI2b6aNrS-swarm-scenario" 'False) (C1 ('MetaCons "ScenarioMetadata" 'PrefixI 'True) (S1 ('MetaSel ('Just "_scenarioVersion") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int) :*: (S1 ('MetaSel ('Just "_scenarioName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "_scenarioAuthor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Text)))))

staticPlacements :: Lens' StaticStructureInfo (Map SubworldName [LocatedStructure]) Source #

A record of the static placements of structures, so that they can be added to the "recognized" list upon scenario initialization

structureDefs :: Lens' StaticStructureInfo [SymmetryAnnotatedGrid StructureCells] Source #

Structure templates that may be auto-recognized when constructed by a robot

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.

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 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 :: (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 :: (Has (Throw SystemFailure) sig m, Has (Lift IO) sig m) => ScenarioInputs -> FilePath -> m Scenario Source #

Load a scenario from a file.

data GameStateInputs Source #

Constructors

GameStateInputs 

Fields

data ScenarioInputs Source #

Constructors

ScenarioInputs 

Fields

  • initWorldMap :: WorldMap

    A collection of typechecked world DSL terms that are available to be used in scenario definitions.

  • initEntityTerrain :: TerrainEntityMaps

    The standard terrain/entity maps loaded from disk. Individual scenarios may define additional terrain/entities which will get added to this map when loading the scenario.

Instances

Instances details
FromJSONE ScenarioInputs Scenario Source # 
Instance details

Defined in Swarm.Game.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