swarm-0.7.0.0: 2D resource gathering game with programmable robots
LicenseBSD-3-Clause
Safe HaskellNone
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 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 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 RowChunkMatchingReference b a Source #

A chunkified version of a structure row. Each unique structure row will need to test one of these against the world row being examined.

data PiecewiseRecognition b a Source #

Constructors

PiecewiseRecognition 

Fields

newtype RowWidth Source #

Constructors

RowWidth Int32 

Instances

Instances details
Eq RowWidth Source # 
Instance details

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

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 Cell and Entity, respectively.

Constructors

StructureRow 

Fields

data ConsolidatedRowReferences b a Source #

Represents all rows across all structures that share a particular row content

data ExtractedArea b a Source #

Instances

Instances details
(Show b, Show a) => Show (ExtractedArea b a) Source # 
Instance details

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

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

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

Methods

(==) :: ExtractedArea b a -> ExtractedArea b a -> Bool #

(/=) :: ExtractedArea b a -> ExtractedArea b a -> Bool #

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 Cell 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

(Eq b, Eq a) => Ord (FoundStructure b a) Source #
STRUCTURE RECOGNIZER CONFLICT RESOLUTION
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

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 
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.7.0.0-IuFfgHrMoE7JrptOBRVOwx-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))))
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.7.0.0-IuFfgHrMoE7JrptOBRVOwx-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 v k Source #

Instances

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

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

Associated Types

type Rep (AutomatonInfo v k) 
Instance details

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

type Rep (AutomatonInfo v k) = D1 ('MetaData "AutomatonInfo" "Swarm.Game.Scenario.Topography.Structure.Recognition.Type" "swarm-0.7.0.0-IuFfgHrMoE7JrptOBRVOwx-swarm-topography" 'False) (C1 ('MetaCons "AutomatonInfo" 'PrefixI 'True) (S1 ('MetaSel ('Just "_inspectionOffsets") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 InspectionOffsets) :*: S1 ('MetaSel ('Just "_piecewiseRecognizer") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (PiecewiseRecognition v k))))

Methods

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

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

type Rep (AutomatonInfo v k) Source # 
Instance details

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

type Rep (AutomatonInfo v k) = D1 ('MetaData "AutomatonInfo" "Swarm.Game.Scenario.Topography.Structure.Recognition.Type" "swarm-0.7.0.0-IuFfgHrMoE7JrptOBRVOwx-swarm-topography" 'False) (C1 ('MetaCons "AutomatonInfo" 'PrefixI 'True) (S1 ('MetaSel ('Just "_inspectionOffsets") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 InspectionOffsets) :*: S1 ('MetaSel ('Just "_piecewiseRecognizer") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (PiecewiseRecognition v k))))

piecewiseRecognizer :: forall v1 k1 v2 k2 f. Functor f => (PiecewiseRecognition v1 k1 -> f (PiecewiseRecognition v2 k2)) -> AutomatonInfo v1 k1 -> f (AutomatonInfo v2 k2) 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) 
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.7.0.0-IuFfgHrMoE7JrptOBRVOwx-swarm-topography" 'False) (C1 ('MetaCons "RecognizerAutomatons" 'PrefixI 'True) (S1 ('MetaSel ('Just "_originalStructureDefinitions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Map StructureName (StructureInfo b a))) :*: S1 ('MetaSel ('Just "_automatonsByEntity") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (HashMap a (AutomatonInfo b a)))))
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.7.0.0-IuFfgHrMoE7JrptOBRVOwx-swarm-topography" 'False) (C1 ('MetaCons "RecognizerAutomatons" 'PrefixI 'True) (S1 ('MetaSel ('Just "_originalStructureDefinitions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Map StructureName (StructureInfo b a))) :*: S1 ('MetaSel ('Just "_automatonsByEntity") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (HashMap a (AutomatonInfo b a)))))

type FoundStructure b a = PositionedStructure (StructureWithGrid 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 Cell and Entity, respectively.

data PositionedStructure s Source #

NOTE: A structure's name + orientation + position will uniquely identify it in the world. Note that position alone is not sufficient; due to transparency, a completely intact smaller structure can co-exist within a larger structure, both sharing the same upper-left coordinate. However, two identical structures (with identical orientation) cannot occupy the same space.

Compare "PositionedStructure OrientedStructure" to: Swarm.Game.Scenario.Topography.Structure.Recognition.Static.LocatedStructure

Instances

Instances details
Functor PositionedStructure Source # 
Instance details

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

ToJSON s => ToJSON (PositionedStructure s) Source # 
Instance details

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

Generic (PositionedStructure s) Source # 
Instance details

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

Associated Types

type Rep (PositionedStructure s) 
Instance details

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

type Rep (PositionedStructure s) = D1 ('MetaData "PositionedStructure" "Swarm.Game.Scenario.Topography.Structure.Recognition.Type" "swarm-0.7.0.0-IuFfgHrMoE7JrptOBRVOwx-swarm-topography" 'False) (C1 ('MetaCons "PositionedStructure" 'PrefixI 'True) (S1 ('MetaSel ('Just "upperLeftCorner") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Cosmic Location)) :*: S1 ('MetaSel ('Just "structureWithGrid") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 s)))
Eq s => Eq (PositionedStructure s) Source # 
Instance details

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

Ord (PositionedStructure OrientedStructure) Source # 
Instance details

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

(Eq b, Eq a) => Ord (FoundStructure b a) Source #
STRUCTURE RECOGNIZER CONFLICT RESOLUTION
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

type Rep (PositionedStructure s) Source # 
Instance details

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

type Rep (PositionedStructure s) = D1 ('MetaData "PositionedStructure" "Swarm.Game.Scenario.Topography.Structure.Recognition.Type" "swarm-0.7.0.0-IuFfgHrMoE7JrptOBRVOwx-swarm-topography" 'False) (C1 ('MetaCons "PositionedStructure" 'PrefixI 'True) (S1 ('MetaSel ('Just "upperLeftCorner") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Cosmic Location)) :*: S1 ('MetaSel ('Just "structureWithGrid") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 s)))

data FoundRowFromChunk a Source #

Instances

Instances details
Functor FoundRowFromChunk Source # 
Instance details

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

ToJSON a => ToJSON (FoundRowFromChunk a) Source # 
Instance details

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

Generic (FoundRowFromChunk a) Source # 
Instance details

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

Associated Types

type Rep (FoundRowFromChunk a) 
Instance details

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

type Rep (FoundRowFromChunk a) = D1 ('MetaData "FoundRowFromChunk" "Swarm.Game.Scenario.Topography.Structure.Recognition.Type" "swarm-0.7.0.0-IuFfgHrMoE7JrptOBRVOwx-swarm-topography" 'False) (C1 ('MetaCons "FoundRowFromChunk" 'PrefixI 'True) (S1 ('MetaSel ('Just "chunkOffsetFromSearchBorder") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int) :*: (S1 ('MetaSel ('Just "horizontalStructPos") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int32) :*: S1 ('MetaSel ('Just "chunkStructure") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 a))))
type Rep (FoundRowFromChunk a) Source # 
Instance details

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

type Rep (FoundRowFromChunk a) = D1 ('MetaData "FoundRowFromChunk" "Swarm.Game.Scenario.Topography.Structure.Recognition.Type" "swarm-0.7.0.0-IuFfgHrMoE7JrptOBRVOwx-swarm-topography" 'False) (C1 ('MetaCons "FoundRowFromChunk" 'PrefixI 'True) (S1 ('MetaSel ('Just "chunkOffsetFromSearchBorder") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int) :*: (S1 ('MetaSel ('Just "horizontalStructPos") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int32) :*: S1 ('MetaSel ('Just "chunkStructure") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 a))))

data FoundAndExpectedChunkPositions Source #

The located occurrences of a specific contiguous chunk of entities. Note that an identical chunk may recur more than once in a structure row. This record represents all of the recurrences of one such chunk.

Any different chunks contained within a row will be described by their own instance of this record.

Instances

Instances details
ToJSON FoundAndExpectedChunkPositions Source # 
Instance details

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

Generic FoundAndExpectedChunkPositions Source # 
Instance details

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

Associated Types

type Rep FoundAndExpectedChunkPositions 
Instance details

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

type Rep FoundAndExpectedChunkPositions = D1 ('MetaData "FoundAndExpectedChunkPositions" "Swarm.Game.Scenario.Topography.Structure.Recognition.Type" "swarm-0.7.0.0-IuFfgHrMoE7JrptOBRVOwx-swarm-topography" 'False) (C1 ('MetaCons "FoundAndExpectedChunkPositions" 'PrefixI 'True) (S1 ('MetaSel ('Just "foundPositions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 NEIntSet) :*: S1 ('MetaSel ('Just "expectedPositions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 NEIntSet)))
type Rep FoundAndExpectedChunkPositions Source # 
Instance details

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

type Rep FoundAndExpectedChunkPositions = D1 ('MetaData "FoundAndExpectedChunkPositions" "Swarm.Game.Scenario.Topography.Structure.Recognition.Type" "swarm-0.7.0.0-IuFfgHrMoE7JrptOBRVOwx-swarm-topography" 'False) (C1 ('MetaCons "FoundAndExpectedChunkPositions" 'PrefixI 'True) (S1 ('MetaSel ('Just "foundPositions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 NEIntSet) :*: S1 ('MetaSel ('Just "expectedPositions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 NEIntSet)))

data ChunkedRowMatch a e Source #

Instances

Instances details
Functor (ChunkedRowMatch a) Source # 
Instance details

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

Methods

fmap :: (a0 -> b) -> ChunkedRowMatch a a0 -> ChunkedRowMatch a b #

(<$) :: a0 -> ChunkedRowMatch a b -> ChunkedRowMatch a a0 #

(ToJSON a, ToJSON e) => ToJSON (ChunkedRowMatch a e) Source # 
Instance details

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

Generic (ChunkedRowMatch a e) Source # 
Instance details

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

Associated Types

type Rep (ChunkedRowMatch a e) 
Instance details

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

type Rep (ChunkedRowMatch a e) = D1 ('MetaData "ChunkedRowMatch" "Swarm.Game.Scenario.Topography.Structure.Recognition.Type" "swarm-0.7.0.0-IuFfgHrMoE7JrptOBRVOwx-swarm-topography" 'False) (C1 ('MetaCons "ChunkedRowMatch" 'PrefixI 'True) (S1 ('MetaSel ('Just "positionsComparison") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [(FoundAndExpectedChunkPositions, NonEmpty e)]) :*: S1 ('MetaSel ('Just "foundChunkRow") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (FoundRowFromChunk a))))

Methods

from :: ChunkedRowMatch a e -> Rep (ChunkedRowMatch a e) x #

to :: Rep (ChunkedRowMatch a e) x -> ChunkedRowMatch a e #

type Rep (ChunkedRowMatch a e) Source # 
Instance details

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

type Rep (ChunkedRowMatch a e) = D1 ('MetaData "ChunkedRowMatch" "Swarm.Game.Scenario.Topography.Structure.Recognition.Type" "swarm-0.7.0.0-IuFfgHrMoE7JrptOBRVOwx-swarm-topography" 'False) (C1 ('MetaCons "ChunkedRowMatch" 'PrefixI 'True) (S1 ('MetaSel ('Just "positionsComparison") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [(FoundAndExpectedChunkPositions, NonEmpty e)]) :*: S1 ('MetaSel ('Just "foundChunkRow") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (FoundRowFromChunk a))))

data EntityDiscrepancy e Source #

Instances

Instances details
Functor EntityDiscrepancy Source # 
Instance details

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

ToJSON e => ToJSON (EntityDiscrepancy e) Source # 
Instance details

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

Generic (EntityDiscrepancy e) Source # 
Instance details

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

Associated Types

type Rep (EntityDiscrepancy e) 
Instance details

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

type Rep (EntityDiscrepancy e) = D1 ('MetaData "EntityDiscrepancy" "Swarm.Game.Scenario.Topography.Structure.Recognition.Type" "swarm-0.7.0.0-IuFfgHrMoE7JrptOBRVOwx-swarm-topography" 'False) (C1 ('MetaCons "EntityDiscrepancy" 'PrefixI 'True) (S1 ('MetaSel ('Just "expectedEntity") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 e) :*: S1 ('MetaSel ('Just "observedEntity") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (AtomicKeySymbol e))))
type Rep (EntityDiscrepancy e) Source # 
Instance details

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

type Rep (EntityDiscrepancy e) = D1 ('MetaData "EntityDiscrepancy" "Swarm.Game.Scenario.Topography.Structure.Recognition.Type" "swarm-0.7.0.0-IuFfgHrMoE7JrptOBRVOwx-swarm-topography" 'False) (C1 ('MetaCons "EntityDiscrepancy" 'PrefixI 'True) (S1 ('MetaSel ('Just "expectedEntity") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 e) :*: S1 ('MetaSel ('Just "observedEntity") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (AtomicKeySymbol e))))

data IntactnessFailureReason e Source #

Instances

Instances details
Functor IntactnessFailureReason Source # 
Instance details

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

ToJSON e => ToJSON (IntactnessFailureReason e) Source # 
Instance details

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

Generic (IntactnessFailureReason e) Source # 
Instance details

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

Associated Types

type Rep (IntactnessFailureReason e) 
Instance details

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

type Rep (IntactnessFailureReason e) = D1 ('MetaData "IntactnessFailureReason" "Swarm.Game.Scenario.Topography.Structure.Recognition.Type" "swarm-0.7.0.0-IuFfgHrMoE7JrptOBRVOwx-swarm-topography" 'False) (C1 ('MetaCons "DiscrepantEntity" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (EntityDiscrepancy e))) :+: C1 ('MetaCons "AlreadyUsedBy" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 OrientedStructure)))
type Rep (IntactnessFailureReason e) Source # 
Instance details

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

type Rep (IntactnessFailureReason e) = D1 ('MetaData "IntactnessFailureReason" "Swarm.Game.Scenario.Topography.Structure.Recognition.Type" "swarm-0.7.0.0-IuFfgHrMoE7JrptOBRVOwx-swarm-topography" 'False) (C1 ('MetaCons "DiscrepantEntity" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (EntityDiscrepancy e))) :+: C1 ('MetaCons "AlreadyUsedBy" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 OrientedStructure)))

data StructureIntactnessFailure e Source #

Instances

Instances details
Functor StructureIntactnessFailure Source # 
Instance details

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

ToJSON e => ToJSON (StructureIntactnessFailure e) Source # 
Instance details

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

Generic (StructureIntactnessFailure e) Source # 
Instance details

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

Associated Types

type Rep (StructureIntactnessFailure e) 
Instance details

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

type Rep (StructureIntactnessFailure e) = D1 ('MetaData "StructureIntactnessFailure" "Swarm.Game.Scenario.Topography.Structure.Recognition.Type" "swarm-0.7.0.0-IuFfgHrMoE7JrptOBRVOwx-swarm-topography" 'False) (C1 ('MetaCons "StructureIntactnessFailure" 'PrefixI 'True) (S1 ('MetaSel ('Just "failedOnIndex") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Location) :*: (S1 ('MetaSel ('Just "totalSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 AreaDimensions) :*: S1 ('MetaSel ('Just "reason") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (IntactnessFailureReason e)))))
type Rep (StructureIntactnessFailure e) Source # 
Instance details

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

type Rep (StructureIntactnessFailure e) = D1 ('MetaData "StructureIntactnessFailure" "Swarm.Game.Scenario.Topography.Structure.Recognition.Type" "swarm-0.7.0.0-IuFfgHrMoE7JrptOBRVOwx-swarm-topography" 'False) (C1 ('MetaCons "StructureIntactnessFailure" 'PrefixI 'True) (S1 ('MetaSel ('Just "failedOnIndex") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Location) :*: (S1 ('MetaSel ('Just "totalSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 AreaDimensions) :*: S1 ('MetaSel ('Just "reason") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (IntactnessFailureReason e)))))

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.

staticAutomatons :: forall b a f. Functor f => (RecognizerAutomatons b a -> f (RecognizerAutomatons b a)) -> StaticStructureInfo b a -> f (StaticStructureInfo b a) Source #

Recognition engine for statically-defined structures

staticPlacements :: forall b a f. Functor f => (Map SubworldName [LocatedStructure] -> f (Map SubworldName [LocatedStructure])) -> StaticStructureInfo b a -> f (StaticStructureInfo b a) Source #

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