License | BSD-3-Clause |
---|---|
Safe Haskell | None |
Language | Haskell2010 |
Swarm.Game.Scenario.Topography.Structure.Recognition.Log
Description
Types strictly for debugging structure recognition via the web interface
Documentation
data ParticipatingEntity e Source #
Constructors
ParticipatingEntity | |
Fields
|
Instances
data IntactPlacementLog e Source #
Constructors
IntactPlacementLog | |
Instances
Functor IntactPlacementLog Source # | |||||
Defined in Swarm.Game.Scenario.Topography.Structure.Recognition.Log Methods fmap :: (a -> b) -> IntactPlacementLog a -> IntactPlacementLog b # (<$) :: a -> IntactPlacementLog b -> IntactPlacementLog a # | |||||
ToJSON e => ToJSON (IntactPlacementLog e) Source # | |||||
Defined in Swarm.Game.Scenario.Topography.Structure.Recognition.Log Methods toJSON :: IntactPlacementLog e -> Value # toEncoding :: IntactPlacementLog e -> Encoding # toJSONList :: [IntactPlacementLog e] -> Value # toEncodingList :: [IntactPlacementLog e] -> Encoding # omitField :: IntactPlacementLog e -> Bool # | |||||
Generic (IntactPlacementLog e) Source # | |||||
Defined in Swarm.Game.Scenario.Topography.Structure.Recognition.Log Associated Types
Methods from :: IntactPlacementLog e -> Rep (IntactPlacementLog e) x # to :: Rep (IntactPlacementLog e) x -> IntactPlacementLog e # | |||||
type Rep (IntactPlacementLog e) Source # | |||||
Defined in Swarm.Game.Scenario.Topography.Structure.Recognition.Log type Rep (IntactPlacementLog e) = D1 ('MetaData "IntactPlacementLog" "Swarm.Game.Scenario.Topography.Structure.Recognition.Log" "swarm-0.7.0.0-IuFfgHrMoE7JrptOBRVOwx-swarm-topography" 'False) (C1 ('MetaCons "IntactPlacementLog" 'PrefixI 'True) (S1 ('MetaSel ('Just "intactnessFailure") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe (StructureIntactnessFailure e))) :*: S1 ('MetaSel ('Just "placedStructure") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (PositionedStructure OrientedStructure)))) |
data ChunkMatchFailureReason e Source #
Constructors
ChunkMatchFailureReason (NonEmpty StructureName) (RowMismatchReason e) |
Instances
Functor ChunkMatchFailureReason Source # | |||||
Defined in Swarm.Game.Scenario.Topography.Structure.Recognition.Log Methods fmap :: (a -> b) -> ChunkMatchFailureReason a -> ChunkMatchFailureReason b # (<$) :: a -> ChunkMatchFailureReason b -> ChunkMatchFailureReason a # | |||||
ToJSON e => ToJSON (ChunkMatchFailureReason e) Source # | |||||
Defined in Swarm.Game.Scenario.Topography.Structure.Recognition.Log Methods toJSON :: ChunkMatchFailureReason e -> Value # toEncoding :: ChunkMatchFailureReason e -> Encoding # toJSONList :: [ChunkMatchFailureReason e] -> Value # toEncodingList :: [ChunkMatchFailureReason e] -> Encoding # omitField :: ChunkMatchFailureReason e -> Bool # | |||||
Generic (ChunkMatchFailureReason e) Source # | |||||
Defined in Swarm.Game.Scenario.Topography.Structure.Recognition.Log Associated Types
Methods from :: ChunkMatchFailureReason e -> Rep (ChunkMatchFailureReason e) x # to :: Rep (ChunkMatchFailureReason e) x -> ChunkMatchFailureReason e # | |||||
type Rep (ChunkMatchFailureReason e) Source # | |||||
Defined in Swarm.Game.Scenario.Topography.Structure.Recognition.Log type Rep (ChunkMatchFailureReason e) = D1 ('MetaData "ChunkMatchFailureReason" "Swarm.Game.Scenario.Topography.Structure.Recognition.Log" "swarm-0.7.0.0-IuFfgHrMoE7JrptOBRVOwx-swarm-topography" 'False) (C1 ('MetaCons "ChunkMatchFailureReason" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (NonEmpty StructureName)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (RowMismatchReason e)))) |
data FoundChunkComparison e Source #
Constructors
FoundChunkComparison | |
Fields
|
Instances
Functor FoundChunkComparison Source # | |||||
Defined in Swarm.Game.Scenario.Topography.Structure.Recognition.Log Methods fmap :: (a -> b) -> FoundChunkComparison a -> FoundChunkComparison b # (<$) :: a -> FoundChunkComparison b -> FoundChunkComparison a # | |||||
ToJSON e => ToJSON (FoundChunkComparison e) Source # | |||||
Defined in Swarm.Game.Scenario.Topography.Structure.Recognition.Log Methods toJSON :: FoundChunkComparison e -> Value # toEncoding :: FoundChunkComparison e -> Encoding # toJSONList :: [FoundChunkComparison e] -> Value # toEncodingList :: [FoundChunkComparison e] -> Encoding # omitField :: FoundChunkComparison e -> Bool # | |||||
Generic (FoundChunkComparison e) Source # | |||||
Defined in Swarm.Game.Scenario.Topography.Structure.Recognition.Log Associated Types
Methods from :: FoundChunkComparison e -> Rep (FoundChunkComparison e) x # to :: Rep (FoundChunkComparison e) x -> FoundChunkComparison e # | |||||
type Rep (FoundChunkComparison e) Source # | |||||
Defined in Swarm.Game.Scenario.Topography.Structure.Recognition.Log type Rep (FoundChunkComparison e) = D1 ('MetaData "FoundChunkComparison" "Swarm.Game.Scenario.Topography.Structure.Recognition.Log" "swarm-0.7.0.0-IuFfgHrMoE7JrptOBRVOwx-swarm-topography" 'False) (C1 ('MetaCons "FoundChunkComparison" 'PrefixI 'True) (S1 ('MetaSel ('Just "foundChunkKeys") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [NonEmpty e]) :*: S1 ('MetaSel ('Just "referenceChunkKeys") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [NonEmpty e]))) |
data RowMismatchReason e Source #
Constructors
NoKeysSubset (FoundChunkComparison e) | |
EmptyIntersection | NOTE: we should never see |
Instances
Functor RowMismatchReason Source # | |||||
Defined in Swarm.Game.Scenario.Topography.Structure.Recognition.Log Methods fmap :: (a -> b) -> RowMismatchReason a -> RowMismatchReason b # (<$) :: a -> RowMismatchReason b -> RowMismatchReason a # | |||||
ToJSON e => ToJSON (RowMismatchReason e) Source # | |||||
Defined in Swarm.Game.Scenario.Topography.Structure.Recognition.Log Methods toJSON :: RowMismatchReason e -> Value # toEncoding :: RowMismatchReason e -> Encoding # toJSONList :: [RowMismatchReason e] -> Value # toEncodingList :: [RowMismatchReason e] -> Encoding # omitField :: RowMismatchReason e -> Bool # | |||||
Generic (RowMismatchReason e) Source # | |||||
Defined in Swarm.Game.Scenario.Topography.Structure.Recognition.Log Associated Types
Methods from :: RowMismatchReason e -> Rep (RowMismatchReason e) x # to :: Rep (RowMismatchReason e) x -> RowMismatchReason e # | |||||
type Rep (RowMismatchReason e) Source # | |||||
Defined in Swarm.Game.Scenario.Topography.Structure.Recognition.Log type Rep (RowMismatchReason e) = D1 ('MetaData "RowMismatchReason" "Swarm.Game.Scenario.Topography.Structure.Recognition.Log" "swarm-0.7.0.0-IuFfgHrMoE7JrptOBRVOwx-swarm-topography" 'False) (C1 ('MetaCons "NoKeysSubset" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (FoundChunkComparison e))) :+: C1 ('MetaCons "EmptyIntersection" 'PrefixI 'False) (U1 :: Type -> Type)) |
Constructors
IntactStaticPlacement [IntactPlacementLog e] | |
StartSearchAt (Cosmic Location) InspectionOffsets | |
FoundParticipatingEntity (ParticipatingEntity e) | |
FoundCompleteStructureCandidates [(OrientedStructure, Cosmic Location)] | |
RecognizedSingleStructure (OrientedStructure, Cosmic Location) | |
FoundPiecewiseChunks [(NonEmpty Int, NonEmpty e)] | this is actually internally used as a (Map (NonEmpty e) (NonEmpty Int)), but the requirements of Functor force us to invert the mapping |
ExpectedChunks (NonEmpty [NonEmpty e]) | |
WorldRowContent [Maybe e] | |
ChunksMatchingExpected [ChunkedRowMatch (NonEmpty StructureName) e] | |
ChunkFailures [ChunkMatchFailureReason e] | |
ChunkIntactnessVerification (IntactPlacementLog e) | |
StructureRemoved StructureName |
Instances
Functor SearchLog Source # | |||||
ToJSON e => ToJSON (SearchLog e) Source # | |||||
Generic (SearchLog e) Source # | |||||
Defined in Swarm.Game.Scenario.Topography.Structure.Recognition.Log Associated Types
| |||||
ToSample (SearchLog e) Source # | |||||
type Rep (SearchLog e) Source # | |||||
Defined in Swarm.Game.Scenario.Topography.Structure.Recognition.Log type Rep (SearchLog e) = D1 ('MetaData "SearchLog" "Swarm.Game.Scenario.Topography.Structure.Recognition.Log" "swarm-0.7.0.0-IuFfgHrMoE7JrptOBRVOwx-swarm-topography" 'False) (((C1 ('MetaCons "IntactStaticPlacement" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [IntactPlacementLog e])) :+: (C1 ('MetaCons "StartSearchAt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Cosmic Location)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 InspectionOffsets)) :+: C1 ('MetaCons "FoundParticipatingEntity" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (ParticipatingEntity e))))) :+: (C1 ('MetaCons "FoundCompleteStructureCandidates" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [(OrientedStructure, Cosmic Location)])) :+: (C1 ('MetaCons "RecognizedSingleStructure" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (OrientedStructure, Cosmic Location))) :+: C1 ('MetaCons "FoundPiecewiseChunks" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [(NonEmpty Int, NonEmpty e)]))))) :+: ((C1 ('MetaCons "ExpectedChunks" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (NonEmpty [NonEmpty e]))) :+: (C1 ('MetaCons "WorldRowContent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Maybe e])) :+: C1 ('MetaCons "ChunksMatchingExpected" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [ChunkedRowMatch (NonEmpty StructureName) e])))) :+: (C1 ('MetaCons "ChunkFailures" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [ChunkMatchFailureReason e])) :+: (C1 ('MetaCons "ChunkIntactnessVerification" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (IntactPlacementLog e))) :+: C1 ('MetaCons "StructureRemoved" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 StructureName)))))) |
data StructureLocation Source #
Constructors
StructureLocation StructureName (Cosmic Location, AbsoluteDir) |
Instances
ToJSON StructureLocation Source # | |||||
Defined in Swarm.Game.Scenario.Topography.Structure.Recognition.Log Methods toJSON :: StructureLocation -> Value # toEncoding :: StructureLocation -> Encoding # toJSONList :: [StructureLocation] -> Value # toEncodingList :: [StructureLocation] -> Encoding # omitField :: StructureLocation -> Bool # | |||||
Generic StructureLocation Source # | |||||
Defined in Swarm.Game.Scenario.Topography.Structure.Recognition.Log Associated Types
Methods from :: StructureLocation -> Rep StructureLocation x # to :: Rep StructureLocation x -> StructureLocation # | |||||
ToSample StructureLocation Source # | |||||
Defined in Swarm.Game.Scenario.Topography.Structure.Recognition.Log Methods toSamples :: Proxy StructureLocation -> [(Text, StructureLocation)] # | |||||
type Rep StructureLocation Source # | |||||
Defined in Swarm.Game.Scenario.Topography.Structure.Recognition.Log type Rep StructureLocation = D1 ('MetaData "StructureLocation" "Swarm.Game.Scenario.Topography.Structure.Recognition.Log" "swarm-0.7.0.0-IuFfgHrMoE7JrptOBRVOwx-swarm-topography" 'False) (C1 ('MetaCons "StructureLocation" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 StructureName) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Cosmic Location, AbsoluteDir)))) |