License | BSD-3-Clause |
---|---|
Safe Haskell | None |
Language | Haskell2010 |
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
- type AtomicKeySymbol a = Maybe a
- type SymbolSequence a = [AtomicKeySymbol a]
- data PositionWithinRow b a = PositionWithinRow {}
- data RowChunkMatchingReference b a = RowChunkMatchingReference {
- locatableRows :: ConsolidatedRowReferences b a
- confirmationMap :: HashMap (NonEmpty a) (NonEmpty Int)
- data PiecewiseRecognition b a = PiecewiseRecognition {
- piecewiseSM :: StateMachine (AtomicKeySymbol a) (NonEmpty a)
- picewiseLookup :: NonEmpty (RowChunkMatchingReference b a)
- data PositionedChunk a = PositionedChunk {
- chunkStartPos :: Int
- chunkContents :: NonEmpty a
- data SingleRowEntityOccurrences b a = SingleRowEntityOccurrences {}
- newtype RowWidth = RowWidth Int32
- data StructureRow b a = StructureRow {
- wholeStructure :: StructureWithGrid b a
- rowIndex :: Int32
- rowContent :: NonEmpty (AtomicKeySymbol a)
- data ConsolidatedRowReferences b a = ConsolidatedRowReferences {
- sharedRowContent :: NonEmpty (AtomicKeySymbol a)
- referencingRows :: NonEmpty (StructureRow b a)
- theRowWidth :: RowWidth
- data ExtractedArea b a = ExtractedArea {}
- data StructureWithGrid b a = StructureWithGrid {
- rotatedTo :: AbsoluteDir
- gridWidth :: RowWidth
- entityGrid :: ExtractedArea b a
- data StructureInfo b a = StructureInfo {}
- data InspectionOffsets = InspectionOffsets {}
- data AutomatonInfo v k = AutomatonInfo {}
- inspectionOffsets :: forall v k f. Functor f => (InspectionOffsets -> f InspectionOffsets) -> AutomatonInfo v k -> f (AutomatonInfo 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)
- data RecognizerAutomatons b a = RecognizerAutomatons {
- _originalStructureDefinitions :: Map StructureName (StructureInfo b a)
- _automatonsByEntity :: HashMap a (AutomatonInfo b a)
- automatonsByEntity :: forall b a f. Functor f => (HashMap a (AutomatonInfo b a) -> f (HashMap a (AutomatonInfo b a))) -> RecognizerAutomatons b a -> f (RecognizerAutomatons b a)
- originalStructureDefinitions :: forall b a f. Functor f => (Map StructureName (StructureInfo b a) -> f (Map StructureName (StructureInfo b a))) -> RecognizerAutomatons b a -> f (RecognizerAutomatons b a)
- type FoundStructure b a = PositionedStructure (StructureWithGrid b a)
- data PositionedStructure s = PositionedStructure {}
- data FoundRowFromChunk a = FoundRowFromChunk {}
- data FoundAndExpectedChunkPositions = FoundAndExpectedChunkPositions {}
- data ChunkedRowMatch a e = ChunkedRowMatch {}
- data EntityDiscrepancy e = EntityDiscrepancy {
- expectedEntity :: e
- observedEntity :: AtomicKeySymbol e
- distillLabel :: StructureWithGrid b a -> OrientedStructure
- data IntactnessFailureReason e
- data StructureIntactnessFailure e = StructureIntactnessFailure {}
- genOccupiedCoords :: FoundStructure b a -> [Cosmic Location]
- data StaticStructureInfo b a = StaticStructureInfo {}
- staticAutomatons :: forall b a f. Functor f => (RecognizerAutomatons b a -> f (RecognizerAutomatons b a)) -> StaticStructureInfo b a -> f (StaticStructureInfo b a)
- staticPlacements :: forall b a f. Functor f => (Map SubworldName [LocatedStructure] -> f (Map SubworldName [LocatedStructure])) -> StaticStructureInfo b a -> f (StaticStructureInfo b a)
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.
Constructors
RowChunkMatchingReference | |
Fields
|
data PiecewiseRecognition b a Source #
Constructors
PiecewiseRecognition | |
Fields
|
data PositionedChunk a Source #
Constructors
PositionedChunk | |
Fields
|
data SingleRowEntityOccurrences b a Source #
Constructors
SingleRowEntityOccurrences | |
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 Cell
and Entity
, respectively.
Constructors
StructureRow | |
Fields
|
data ConsolidatedRowReferences b a Source #
Represents all rows across all structures that share a particular row content
Constructors
ConsolidatedRowReferences | |
Fields
|
data ExtractedArea b a Source #
Constructors
ExtractedArea | |
Fields
|
Instances
(Show b, Show a) => Show (ExtractedArea b a) Source # | |
Defined in Swarm.Game.Scenario.Topography.Structure.Recognition.Type Methods showsPrec :: Int -> ExtractedArea b a -> ShowS # show :: ExtractedArea b a -> String # showList :: [ExtractedArea b a] -> ShowS # | |
(Eq b, Eq a) => Eq (ExtractedArea b a) Source # | |
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.
Constructors
StructureWithGrid | |
Fields
|
Instances
(Eq b, Eq a) => Eq (StructureWithGrid b a) Source # | |
Defined in Swarm.Game.Scenario.Topography.Structure.Recognition.Type Methods (==) :: StructureWithGrid b a -> StructureWithGrid b a -> Bool # (/=) :: StructureWithGrid b a -> StructureWithGrid b a -> Bool # | |
(Eq b, Eq a) => Ord (FoundStructure b a) Source # |
Since the natural order of coordinates increases as described,
we need to invert it with |
Defined in Swarm.Game.Scenario.Topography.Structure.Recognition.Type Methods compare :: FoundStructure b a -> FoundStructure b a -> Ordering # (<) :: FoundStructure b a -> FoundStructure b a -> Bool # (<=) :: FoundStructure b a -> FoundStructure b a -> Bool # (>) :: FoundStructure b a -> FoundStructure b a -> Bool # (>=) :: FoundStructure b a -> FoundStructure b a -> Bool # max :: FoundStructure b a -> FoundStructure b a -> FoundStructure b a # min :: FoundStructure b a -> FoundStructure b a -> FoundStructure b a # |
data StructureInfo b a Source #
Structure definitions with precomputed metadata for consumption by the UI
Constructors
StructureInfo | |
Fields
|
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
|
Instances
data AutomatonInfo v k Source #
Constructors
AutomatonInfo | |
Fields |
Instances
Generic (AutomatonInfo v k) Source # | |||||
Defined in Swarm.Game.Scenario.Topography.Structure.Recognition.Type Associated Types
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 # | |||||
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)))) |
inspectionOffsets :: forall v k f. Functor f => (InspectionOffsets -> f InspectionOffsets) -> AutomatonInfo v k -> f (AutomatonInfo v k) Source #
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
Generic (RecognizerAutomatons b a) Source # | |||||
Defined in Swarm.Game.Scenario.Topography.Structure.Recognition.Type Associated Types
Methods from :: RecognizerAutomatons b a -> Rep (RecognizerAutomatons b a) x # to :: Rep (RecognizerAutomatons b a) x -> RecognizerAutomatons b a # | |||||
type Rep (RecognizerAutomatons b a) Source # | |||||
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))))) |
automatonsByEntity :: forall b a f. Functor f => (HashMap a (AutomatonInfo b a) -> f (HashMap a (AutomatonInfo b a))) -> RecognizerAutomatons b a -> f (RecognizerAutomatons b a) Source #
originalStructureDefinitions :: forall b a f. Functor f => (Map StructureName (StructureInfo b a) -> f (Map StructureName (StructureInfo b a))) -> RecognizerAutomatons b a -> f (RecognizerAutomatons b a) Source #
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
Constructors
PositionedStructure | |
Fields |
Instances
Functor PositionedStructure Source # | |||||
Defined in Swarm.Game.Scenario.Topography.Structure.Recognition.Type Methods fmap :: (a -> b) -> PositionedStructure a -> PositionedStructure b # (<$) :: a -> PositionedStructure b -> PositionedStructure a # | |||||
ToJSON s => ToJSON (PositionedStructure s) Source # | |||||
Defined in Swarm.Game.Scenario.Topography.Structure.Recognition.Type Methods toJSON :: PositionedStructure s -> Value # toEncoding :: PositionedStructure s -> Encoding # toJSONList :: [PositionedStructure s] -> Value # toEncodingList :: [PositionedStructure s] -> Encoding # omitField :: PositionedStructure s -> Bool # | |||||
Generic (PositionedStructure s) Source # | |||||
Defined in Swarm.Game.Scenario.Topography.Structure.Recognition.Type Associated Types
Methods from :: PositionedStructure s -> Rep (PositionedStructure s) x # to :: Rep (PositionedStructure s) x -> PositionedStructure s # | |||||
Eq s => Eq (PositionedStructure s) Source # | |||||
Defined in Swarm.Game.Scenario.Topography.Structure.Recognition.Type Methods (==) :: PositionedStructure s -> PositionedStructure s -> Bool # (/=) :: PositionedStructure s -> PositionedStructure s -> Bool # | |||||
Ord (PositionedStructure OrientedStructure) Source # | |||||
Defined in Swarm.Game.Scenario.Topography.Structure.Recognition.Type Methods compare :: PositionedStructure OrientedStructure -> PositionedStructure OrientedStructure -> Ordering # (<) :: PositionedStructure OrientedStructure -> PositionedStructure OrientedStructure -> Bool # (<=) :: PositionedStructure OrientedStructure -> PositionedStructure OrientedStructure -> Bool # (>) :: PositionedStructure OrientedStructure -> PositionedStructure OrientedStructure -> Bool # (>=) :: PositionedStructure OrientedStructure -> PositionedStructure OrientedStructure -> Bool # max :: PositionedStructure OrientedStructure -> PositionedStructure OrientedStructure -> PositionedStructure OrientedStructure # min :: PositionedStructure OrientedStructure -> PositionedStructure OrientedStructure -> PositionedStructure OrientedStructure # | |||||
(Eq b, Eq a) => Ord (FoundStructure b a) Source # |
Since the natural order of coordinates increases as described,
we need to invert it with | ||||
Defined in Swarm.Game.Scenario.Topography.Structure.Recognition.Type Methods compare :: FoundStructure b a -> FoundStructure b a -> Ordering # (<) :: FoundStructure b a -> FoundStructure b a -> Bool # (<=) :: FoundStructure b a -> FoundStructure b a -> Bool # (>) :: FoundStructure b a -> FoundStructure b a -> Bool # (>=) :: FoundStructure b a -> FoundStructure b a -> Bool # max :: FoundStructure b a -> FoundStructure b a -> FoundStructure b a # min :: FoundStructure b a -> FoundStructure b a -> FoundStructure b a # | |||||
type Rep (PositionedStructure s) Source # | |||||
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 #
Constructors
FoundRowFromChunk | |
Fields |
Instances
Functor FoundRowFromChunk Source # | |||||
Defined in Swarm.Game.Scenario.Topography.Structure.Recognition.Type Methods fmap :: (a -> b) -> FoundRowFromChunk a -> FoundRowFromChunk b # (<$) :: a -> FoundRowFromChunk b -> FoundRowFromChunk a # | |||||
ToJSON a => ToJSON (FoundRowFromChunk a) Source # | |||||
Defined in Swarm.Game.Scenario.Topography.Structure.Recognition.Type Methods toJSON :: FoundRowFromChunk a -> Value # toEncoding :: FoundRowFromChunk a -> Encoding # toJSONList :: [FoundRowFromChunk a] -> Value # toEncodingList :: [FoundRowFromChunk a] -> Encoding # omitField :: FoundRowFromChunk a -> Bool # | |||||
Generic (FoundRowFromChunk a) Source # | |||||
Defined in Swarm.Game.Scenario.Topography.Structure.Recognition.Type Associated Types
Methods from :: FoundRowFromChunk a -> Rep (FoundRowFromChunk a) x # to :: Rep (FoundRowFromChunk a) x -> FoundRowFromChunk a # | |||||
type Rep (FoundRowFromChunk a) Source # | |||||
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.
Constructors
FoundAndExpectedChunkPositions | |
Fields |
Instances
ToJSON FoundAndExpectedChunkPositions Source # | |||||
Generic FoundAndExpectedChunkPositions Source # | |||||
Defined in Swarm.Game.Scenario.Topography.Structure.Recognition.Type Associated Types
| |||||
type Rep FoundAndExpectedChunkPositions Source # | |||||
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 #
Constructors
ChunkedRowMatch | |
Fields |
Instances
Functor (ChunkedRowMatch a) Source # | |||||
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 # | |||||
Defined in Swarm.Game.Scenario.Topography.Structure.Recognition.Type Methods toJSON :: ChunkedRowMatch a e -> Value # toEncoding :: ChunkedRowMatch a e -> Encoding # toJSONList :: [ChunkedRowMatch a e] -> Value # toEncodingList :: [ChunkedRowMatch a e] -> Encoding # omitField :: ChunkedRowMatch a e -> Bool # | |||||
Generic (ChunkedRowMatch a e) Source # | |||||
Defined in Swarm.Game.Scenario.Topography.Structure.Recognition.Type Associated Types
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 # | |||||
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 #
Constructors
EntityDiscrepancy | |
Fields
|
Instances
Functor EntityDiscrepancy Source # | |||||
Defined in Swarm.Game.Scenario.Topography.Structure.Recognition.Type Methods fmap :: (a -> b) -> EntityDiscrepancy a -> EntityDiscrepancy b # (<$) :: a -> EntityDiscrepancy b -> EntityDiscrepancy a # | |||||
ToJSON e => ToJSON (EntityDiscrepancy e) Source # | |||||
Defined in Swarm.Game.Scenario.Topography.Structure.Recognition.Type Methods toJSON :: EntityDiscrepancy e -> Value # toEncoding :: EntityDiscrepancy e -> Encoding # toJSONList :: [EntityDiscrepancy e] -> Value # toEncodingList :: [EntityDiscrepancy e] -> Encoding # omitField :: EntityDiscrepancy e -> Bool # | |||||
Generic (EntityDiscrepancy e) Source # | |||||
Defined in Swarm.Game.Scenario.Topography.Structure.Recognition.Type Associated Types
Methods from :: EntityDiscrepancy e -> Rep (EntityDiscrepancy e) x # to :: Rep (EntityDiscrepancy e) x -> EntityDiscrepancy e # | |||||
type Rep (EntityDiscrepancy e) Source # | |||||
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)))) |
distillLabel :: StructureWithGrid b a -> OrientedStructure Source #
data IntactnessFailureReason e Source #
Constructors
DiscrepantEntity (EntityDiscrepancy e) | |
AlreadyUsedBy OrientedStructure |
Instances
Functor IntactnessFailureReason Source # | |||||
Defined in Swarm.Game.Scenario.Topography.Structure.Recognition.Type Methods fmap :: (a -> b) -> IntactnessFailureReason a -> IntactnessFailureReason b # (<$) :: a -> IntactnessFailureReason b -> IntactnessFailureReason a # | |||||
ToJSON e => ToJSON (IntactnessFailureReason e) Source # | |||||
Defined in Swarm.Game.Scenario.Topography.Structure.Recognition.Type Methods toJSON :: IntactnessFailureReason e -> Value # toEncoding :: IntactnessFailureReason e -> Encoding # toJSONList :: [IntactnessFailureReason e] -> Value # toEncodingList :: [IntactnessFailureReason e] -> Encoding # omitField :: IntactnessFailureReason e -> Bool # | |||||
Generic (IntactnessFailureReason e) Source # | |||||
Defined in Swarm.Game.Scenario.Topography.Structure.Recognition.Type Associated Types
Methods from :: IntactnessFailureReason e -> Rep (IntactnessFailureReason e) x # to :: Rep (IntactnessFailureReason e) x -> IntactnessFailureReason e # | |||||
type Rep (IntactnessFailureReason e) Source # | |||||
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 #
Constructors
StructureIntactnessFailure | |
Fields |
Instances
Functor StructureIntactnessFailure Source # | |||||
Defined in Swarm.Game.Scenario.Topography.Structure.Recognition.Type Methods fmap :: (a -> b) -> StructureIntactnessFailure a -> StructureIntactnessFailure b # (<$) :: a -> StructureIntactnessFailure b -> StructureIntactnessFailure a # | |||||
ToJSON e => ToJSON (StructureIntactnessFailure e) Source # | |||||
Defined in Swarm.Game.Scenario.Topography.Structure.Recognition.Type Methods toJSON :: StructureIntactnessFailure e -> Value # toEncoding :: StructureIntactnessFailure e -> Encoding # toJSONList :: [StructureIntactnessFailure e] -> Value # toEncodingList :: [StructureIntactnessFailure e] -> Encoding # omitField :: StructureIntactnessFailure e -> Bool # | |||||
Generic (StructureIntactnessFailure e) Source # | |||||
Defined in Swarm.Game.Scenario.Topography.Structure.Recognition.Type Associated Types
Methods from :: StructureIntactnessFailure e -> Rep (StructureIntactnessFailure e) x # to :: Rep (StructureIntactnessFailure e) x -> StructureIntactnessFailure e # | |||||
type Rep (StructureIntactnessFailure e) Source # | |||||
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.
data StaticStructureInfo b a Source #
Constructors
StaticStructureInfo | |
Fields |
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