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

Swarm.Game.Scenario.Topography.Structure.Recognition.Type

Description

Structure recognizer types.

See overview of the structure recognizer feature in Swarm.Game.Scenario.Topography.Structure.Recognition.Precompute.

The following structure template shall be used to illustrate roles of the types in this module:

cdc
aab
cdc
Synopsis

Documentation

type OriginalName = Text Source #

A NamedStructure has its own newtype name (StructureName), but we standardize on Text here to avoid parameterizing our NamedOriginal datatype on bespoke name types.

type AtomicKeySymbol a = Maybe a Source #

A "needle" consisting of a single cell within the haystack (a row of cells) to be searched.

Example

A single entity a in the row:

aab

type SymbolSequence a = [AtomicKeySymbol a] Source #

A "needle" consisting row of cells within the haystack (a sequence of rows) to be searched.

Example

The complete row:

aab

data StructureSearcher b a Source #

This is returned as a value of the 1-D searcher. It contains search automatons customized to the 2-D structures that may possibly contain the row found by the 1-D searcher.

data PositionWithinRow b a Source #

Position specific to a single entity within a horizontal row.

Example

For entity b within the row:

aab

Its _position is 2.

Constructors

PositionWithinRow 

Fields

data StructureRow b a Source #

A a specific row within a particular structure.

Example

For the second occurrence of cdc within the structure:

cdc
aab
cdc

it's rowIndex is 2.

The two type parameters, b and a, correspond to StructureCells and Entity, respectively.

Constructors

StructureRow 

Fields

data NamedOriginal a Source #

This wrapper facilitates naming the original structure (i.e. the "payload" for recognition) for the purpose of both UI display and internal uniqueness, while remaining agnostic to its internals.

Constructors

NamedOriginal 

Fields

data StructureWithGrid b a Source #

The original definition of a structure, bundled with its grid of cells having been extracted for convenience.

The two type parameters, b and a, correspond to StructureCells and Entity, respectively.

Instances

Instances details
(Eq b, Eq a) => Eq (StructureWithGrid b a) Source # 
Instance details

Defined in Swarm.Game.Scenario.Topography.Structure.Recognition.Type

data RotationalSymmetry Source #

Constructors

NoSymmetry

Aka 1-fold symmetry

TwoFold

Equivalent under rotation by 180 degrees

FourFold

Equivalent under rotation by 90 degrees

data StructureInfo b a Source #

Structure definitions with precomputed metadata for consumption by the UI

data InspectionOffsets Source #

For all of the rows that contain a given entity (and are recognized by a single automaton), compute the left-most and right-most position within the row that the given entity may occur.

This determines how far to the left and to the right our search of the world cells needs to begin and end, respectively.

The Semigroup instance always grows in extent, taking the minimum of the leftward offsets and the maximum of the rightward offsets.

Constructors

InspectionOffsets 

Fields

  • startOffset :: Min Int32

    Always non-positive (i.e. either zero or negative). For the first-level search, this extends to the left. For the second-level search, this extends upward.

  • endOffset :: Max Int32

    Always non-negative. For the first-level search, this extends to the right. For the second-level search, this extends downward.

Instances

Instances details
ToJSON InspectionOffsets Source # 
Instance details

Defined in Swarm.Game.Scenario.Topography.Structure.Recognition.Type

Semigroup InspectionOffsets Source # 
Instance details

Defined in Swarm.Game.Scenario.Topography.Structure.Recognition.Type

Generic InspectionOffsets Source # 
Instance details

Defined in Swarm.Game.Scenario.Topography.Structure.Recognition.Type

Associated Types

type Rep InspectionOffsets :: Type -> Type #

Show InspectionOffsets Source # 
Instance details

Defined in Swarm.Game.Scenario.Topography.Structure.Recognition.Type

type Rep InspectionOffsets Source # 
Instance details

Defined in Swarm.Game.Scenario.Topography.Structure.Recognition.Type

type Rep InspectionOffsets = D1 ('MetaData "InspectionOffsets" "Swarm.Game.Scenario.Topography.Structure.Recognition.Type" "swarm-0.6.0.0-ERx1HMcRMba59aI2b6aNrS-swarm-topography" 'False) (C1 ('MetaCons "InspectionOffsets" 'PrefixI 'True) (S1 ('MetaSel ('Just "startOffset") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Min Int32)) :*: S1 ('MetaSel ('Just "endOffset") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Max Int32))))

data AutomatonInfo en k v Source #

Each automaton shall be initialized to recognize a certain subset of structure rows, that may either all be within one structure, or span multiple structures.

Instances

Instances details
Generic (AutomatonInfo en k v) Source # 
Instance details

Defined in Swarm.Game.Scenario.Topography.Structure.Recognition.Type

Associated Types

type Rep (AutomatonInfo en k v) :: Type -> Type #

Methods

from :: AutomatonInfo en k v -> Rep (AutomatonInfo en k v) x #

to :: Rep (AutomatonInfo en k v) x -> AutomatonInfo en k v #

type Rep (AutomatonInfo en k v) Source # 
Instance details

Defined in Swarm.Game.Scenario.Topography.Structure.Recognition.Type

type Rep (AutomatonInfo en k v) = D1 ('MetaData "AutomatonInfo" "Swarm.Game.Scenario.Topography.Structure.Recognition.Type" "swarm-0.6.0.0-ERx1HMcRMba59aI2b6aNrS-swarm-topography" 'False) (C1 ('MetaCons "AutomatonInfo" 'PrefixI 'True) (S1 ('MetaSel ('Just "_participatingEntities") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (HashSet en)) :*: (S1 ('MetaSel ('Just "_inspectionOffsets") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 InspectionOffsets) :*: S1 ('MetaSel ('Just "_automaton") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (StateMachine k v)))))

participatingEntities :: forall en k v en. Lens (AutomatonInfo en k v) (AutomatonInfo en k v) (HashSet en) (HashSet en) Source #

automaton :: forall en k v k v. Lens (AutomatonInfo en k v) (AutomatonInfo en k v) (StateMachine k v) (StateMachine k v) Source #

data RecognizerAutomatons b a Source #

The complete set of data needed to identify applicable structures, based on a just-placed entity.

Constructors

RecognizerAutomatons 

Fields

Instances

Instances details
Generic (RecognizerAutomatons b a) Source # 
Instance details

Defined in Swarm.Game.Scenario.Topography.Structure.Recognition.Type

Associated Types

type Rep (RecognizerAutomatons b a) :: Type -> Type #

type Rep (RecognizerAutomatons b a) Source # 
Instance details

Defined in Swarm.Game.Scenario.Topography.Structure.Recognition.Type

type Rep (RecognizerAutomatons b a) = D1 ('MetaData "RecognizerAutomatons" "Swarm.Game.Scenario.Topography.Structure.Recognition.Type" "swarm-0.6.0.0-ERx1HMcRMba59aI2b6aNrS-swarm-topography" 'False) (C1 ('MetaCons "RecognizerAutomatons" 'PrefixI 'True) (S1 ('MetaSel ('Just "_originalStructureDefinitions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Map OriginalName (StructureInfo b a))) :*: S1 ('MetaSel ('Just "_automatonsByEntity") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (HashMap a (AutomatonInfo a (AtomicKeySymbol a) (StructureSearcher b a))))))

data FoundStructure b a Source #

Final output of the search process. These are the elements that are stored in the FoundRegistry.

The two type parameters, b and a, correspond to StructureCells and Entity, respectively.

Instances

Instances details
(Eq b, Eq a) => Eq (FoundStructure b a) Source # 
Instance details

Defined in Swarm.Game.Scenario.Topography.Structure.Recognition.Type

(Eq b, Eq a) => Ord (FoundStructure b a) Source #

Ordering is by increasing preference between simultaneously completed structures. The preference heuristic is for:

  1. Primarily, larger area.
  2. Secondarily, lower X-Y coords (X is compared first)

Since the natural order of coordinates increases as described, we need to invert it with Down so that this ordering is by increasing preference.

Instance details

Defined in Swarm.Game.Scenario.Topography.Structure.Recognition.Type

genOccupiedCoords :: FoundStructure b a -> [Cosmic Location] Source #

Yields coordinates that are occupied by an entity of a placed structure. Cells within the rectangular bounds of the structure that are unoccupied are not included.