module Swarm.Game.Scenario.Topography.Structure.Recognition.Log where
import Data.Aeson
import Data.Int (Int32)
import GHC.Generics (Generic)
import Servant.Docs (ToSample)
import Servant.Docs qualified as SD
import Swarm.Game.Location (Location)
import Swarm.Game.Scenario.Topography.Structure.Recognition.Type
import Swarm.Game.Universe (Cosmic)
type StructureRowContent e = [Maybe e]
type WorldRowContent e = [Maybe e]
data MatchingRowFrom = MatchingRowFrom
{ MatchingRowFrom -> Int32
rowIdx :: Int32
, MatchingRowFrom -> OriginalName
structure :: OriginalName
}
deriving ((forall x. MatchingRowFrom -> Rep MatchingRowFrom x)
-> (forall x. Rep MatchingRowFrom x -> MatchingRowFrom)
-> Generic MatchingRowFrom
forall x. Rep MatchingRowFrom x -> MatchingRowFrom
forall x. MatchingRowFrom -> Rep MatchingRowFrom x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. MatchingRowFrom -> Rep MatchingRowFrom x
from :: forall x. MatchingRowFrom -> Rep MatchingRowFrom x
$cto :: forall x. Rep MatchingRowFrom x -> MatchingRowFrom
to :: forall x. Rep MatchingRowFrom x -> MatchingRowFrom
Generic, [MatchingRowFrom] -> Value
[MatchingRowFrom] -> Encoding
MatchingRowFrom -> Bool
MatchingRowFrom -> Value
MatchingRowFrom -> Encoding
(MatchingRowFrom -> Value)
-> (MatchingRowFrom -> Encoding)
-> ([MatchingRowFrom] -> Value)
-> ([MatchingRowFrom] -> Encoding)
-> (MatchingRowFrom -> Bool)
-> ToJSON MatchingRowFrom
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: MatchingRowFrom -> Value
toJSON :: MatchingRowFrom -> Value
$ctoEncoding :: MatchingRowFrom -> Encoding
toEncoding :: MatchingRowFrom -> Encoding
$ctoJSONList :: [MatchingRowFrom] -> Value
toJSONList :: [MatchingRowFrom] -> Value
$ctoEncodingList :: [MatchingRowFrom] -> Encoding
toEncodingList :: [MatchingRowFrom] -> Encoding
$comitField :: MatchingRowFrom -> Bool
omitField :: MatchingRowFrom -> Bool
ToJSON)
newtype HaystackPosition = HaystackPosition Int
deriving ((forall x. HaystackPosition -> Rep HaystackPosition x)
-> (forall x. Rep HaystackPosition x -> HaystackPosition)
-> Generic HaystackPosition
forall x. Rep HaystackPosition x -> HaystackPosition
forall x. HaystackPosition -> Rep HaystackPosition x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. HaystackPosition -> Rep HaystackPosition x
from :: forall x. HaystackPosition -> Rep HaystackPosition x
$cto :: forall x. Rep HaystackPosition x -> HaystackPosition
to :: forall x. Rep HaystackPosition x -> HaystackPosition
Generic, [HaystackPosition] -> Value
[HaystackPosition] -> Encoding
HaystackPosition -> Bool
HaystackPosition -> Value
HaystackPosition -> Encoding
(HaystackPosition -> Value)
-> (HaystackPosition -> Encoding)
-> ([HaystackPosition] -> Value)
-> ([HaystackPosition] -> Encoding)
-> (HaystackPosition -> Bool)
-> ToJSON HaystackPosition
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: HaystackPosition -> Value
toJSON :: HaystackPosition -> Value
$ctoEncoding :: HaystackPosition -> Encoding
toEncoding :: HaystackPosition -> Encoding
$ctoJSONList :: [HaystackPosition] -> Value
toJSONList :: [HaystackPosition] -> Value
$ctoEncodingList :: [HaystackPosition] -> Encoding
toEncodingList :: [HaystackPosition] -> Encoding
$comitField :: HaystackPosition -> Bool
omitField :: HaystackPosition -> Bool
ToJSON)
data HaystackContext e = HaystackContext
{ forall e. HaystackContext e -> WorldRowContent e
worldRow :: WorldRowContent e
, forall e. HaystackContext e -> HaystackPosition
haystackPosition :: HaystackPosition
}
deriving ((forall a b. (a -> b) -> HaystackContext a -> HaystackContext b)
-> (forall a b. a -> HaystackContext b -> HaystackContext a)
-> Functor HaystackContext
forall a b. a -> HaystackContext b -> HaystackContext a
forall a b. (a -> b) -> HaystackContext a -> HaystackContext b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall a b. (a -> b) -> HaystackContext a -> HaystackContext b
fmap :: forall a b. (a -> b) -> HaystackContext a -> HaystackContext b
$c<$ :: forall a b. a -> HaystackContext b -> HaystackContext a
<$ :: forall a b. a -> HaystackContext b -> HaystackContext a
Functor, (forall x. HaystackContext e -> Rep (HaystackContext e) x)
-> (forall x. Rep (HaystackContext e) x -> HaystackContext e)
-> Generic (HaystackContext e)
forall x. Rep (HaystackContext e) x -> HaystackContext e
forall x. HaystackContext e -> Rep (HaystackContext e) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall e x. Rep (HaystackContext e) x -> HaystackContext e
forall e x. HaystackContext e -> Rep (HaystackContext e) x
$cfrom :: forall e x. HaystackContext e -> Rep (HaystackContext e) x
from :: forall x. HaystackContext e -> Rep (HaystackContext e) x
$cto :: forall e x. Rep (HaystackContext e) x -> HaystackContext e
to :: forall x. Rep (HaystackContext e) x -> HaystackContext e
Generic, [HaystackContext e] -> Value
[HaystackContext e] -> Encoding
HaystackContext e -> Bool
HaystackContext e -> Value
HaystackContext e -> Encoding
(HaystackContext e -> Value)
-> (HaystackContext e -> Encoding)
-> ([HaystackContext e] -> Value)
-> ([HaystackContext e] -> Encoding)
-> (HaystackContext e -> Bool)
-> ToJSON (HaystackContext e)
forall e. ToJSON e => [HaystackContext e] -> Value
forall e. ToJSON e => [HaystackContext e] -> Encoding
forall e. ToJSON e => HaystackContext e -> Bool
forall e. ToJSON e => HaystackContext e -> Value
forall e. ToJSON e => HaystackContext e -> Encoding
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: forall e. ToJSON e => HaystackContext e -> Value
toJSON :: HaystackContext e -> Value
$ctoEncoding :: forall e. ToJSON e => HaystackContext e -> Encoding
toEncoding :: HaystackContext e -> Encoding
$ctoJSONList :: forall e. ToJSON e => [HaystackContext e] -> Value
toJSONList :: [HaystackContext e] -> Value
$ctoEncodingList :: forall e. ToJSON e => [HaystackContext e] -> Encoding
toEncodingList :: [HaystackContext e] -> Encoding
$comitField :: forall e. ToJSON e => HaystackContext e -> Bool
omitField :: HaystackContext e -> Bool
ToJSON)
data FoundRowCandidate e = FoundRowCandidate
{ forall e. FoundRowCandidate e -> HaystackContext e
haystackContext :: HaystackContext e
, forall e. FoundRowCandidate e -> StructureRowContent e
structureContent :: StructureRowContent e
, forall e. FoundRowCandidate e -> [MatchingRowFrom]
rowCandidates :: [MatchingRowFrom]
}
deriving ((forall a b.
(a -> b) -> FoundRowCandidate a -> FoundRowCandidate b)
-> (forall a b. a -> FoundRowCandidate b -> FoundRowCandidate a)
-> Functor FoundRowCandidate
forall a b. a -> FoundRowCandidate b -> FoundRowCandidate a
forall a b. (a -> b) -> FoundRowCandidate a -> FoundRowCandidate b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall a b. (a -> b) -> FoundRowCandidate a -> FoundRowCandidate b
fmap :: forall a b. (a -> b) -> FoundRowCandidate a -> FoundRowCandidate b
$c<$ :: forall a b. a -> FoundRowCandidate b -> FoundRowCandidate a
<$ :: forall a b. a -> FoundRowCandidate b -> FoundRowCandidate a
Functor, (forall x. FoundRowCandidate e -> Rep (FoundRowCandidate e) x)
-> (forall x. Rep (FoundRowCandidate e) x -> FoundRowCandidate e)
-> Generic (FoundRowCandidate e)
forall x. Rep (FoundRowCandidate e) x -> FoundRowCandidate e
forall x. FoundRowCandidate e -> Rep (FoundRowCandidate e) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall e x. Rep (FoundRowCandidate e) x -> FoundRowCandidate e
forall e x. FoundRowCandidate e -> Rep (FoundRowCandidate e) x
$cfrom :: forall e x. FoundRowCandidate e -> Rep (FoundRowCandidate e) x
from :: forall x. FoundRowCandidate e -> Rep (FoundRowCandidate e) x
$cto :: forall e x. Rep (FoundRowCandidate e) x -> FoundRowCandidate e
to :: forall x. Rep (FoundRowCandidate e) x -> FoundRowCandidate e
Generic, [FoundRowCandidate e] -> Value
[FoundRowCandidate e] -> Encoding
FoundRowCandidate e -> Bool
FoundRowCandidate e -> Value
FoundRowCandidate e -> Encoding
(FoundRowCandidate e -> Value)
-> (FoundRowCandidate e -> Encoding)
-> ([FoundRowCandidate e] -> Value)
-> ([FoundRowCandidate e] -> Encoding)
-> (FoundRowCandidate e -> Bool)
-> ToJSON (FoundRowCandidate e)
forall e. ToJSON e => [FoundRowCandidate e] -> Value
forall e. ToJSON e => [FoundRowCandidate e] -> Encoding
forall e. ToJSON e => FoundRowCandidate e -> Bool
forall e. ToJSON e => FoundRowCandidate e -> Value
forall e. ToJSON e => FoundRowCandidate e -> Encoding
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: forall e. ToJSON e => FoundRowCandidate e -> Value
toJSON :: FoundRowCandidate e -> Value
$ctoEncoding :: forall e. ToJSON e => FoundRowCandidate e -> Encoding
toEncoding :: FoundRowCandidate e -> Encoding
$ctoJSONList :: forall e. ToJSON e => [FoundRowCandidate e] -> Value
toJSONList :: [FoundRowCandidate e] -> Value
$ctoEncodingList :: forall e. ToJSON e => [FoundRowCandidate e] -> Encoding
toEncodingList :: [FoundRowCandidate e] -> Encoding
$comitField :: forall e. ToJSON e => FoundRowCandidate e -> Bool
omitField :: FoundRowCandidate e -> Bool
ToJSON)
data ParticipatingEntity e = ParticipatingEntity
{ forall e. ParticipatingEntity e -> e
entity :: e
, forall e. ParticipatingEntity e -> InspectionOffsets
searchOffsets :: InspectionOffsets
}
deriving ((forall a b.
(a -> b) -> ParticipatingEntity a -> ParticipatingEntity b)
-> (forall a b.
a -> ParticipatingEntity b -> ParticipatingEntity a)
-> Functor ParticipatingEntity
forall a b. a -> ParticipatingEntity b -> ParticipatingEntity a
forall a b.
(a -> b) -> ParticipatingEntity a -> ParticipatingEntity b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall a b.
(a -> b) -> ParticipatingEntity a -> ParticipatingEntity b
fmap :: forall a b.
(a -> b) -> ParticipatingEntity a -> ParticipatingEntity b
$c<$ :: forall a b. a -> ParticipatingEntity b -> ParticipatingEntity a
<$ :: forall a b. a -> ParticipatingEntity b -> ParticipatingEntity a
Functor, (forall x. ParticipatingEntity e -> Rep (ParticipatingEntity e) x)
-> (forall x.
Rep (ParticipatingEntity e) x -> ParticipatingEntity e)
-> Generic (ParticipatingEntity e)
forall x. Rep (ParticipatingEntity e) x -> ParticipatingEntity e
forall x. ParticipatingEntity e -> Rep (ParticipatingEntity e) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall e x. Rep (ParticipatingEntity e) x -> ParticipatingEntity e
forall e x. ParticipatingEntity e -> Rep (ParticipatingEntity e) x
$cfrom :: forall e x. ParticipatingEntity e -> Rep (ParticipatingEntity e) x
from :: forall x. ParticipatingEntity e -> Rep (ParticipatingEntity e) x
$cto :: forall e x. Rep (ParticipatingEntity e) x -> ParticipatingEntity e
to :: forall x. Rep (ParticipatingEntity e) x -> ParticipatingEntity e
Generic, [ParticipatingEntity e] -> Value
[ParticipatingEntity e] -> Encoding
ParticipatingEntity e -> Bool
ParticipatingEntity e -> Value
ParticipatingEntity e -> Encoding
(ParticipatingEntity e -> Value)
-> (ParticipatingEntity e -> Encoding)
-> ([ParticipatingEntity e] -> Value)
-> ([ParticipatingEntity e] -> Encoding)
-> (ParticipatingEntity e -> Bool)
-> ToJSON (ParticipatingEntity e)
forall e. ToJSON e => [ParticipatingEntity e] -> Value
forall e. ToJSON e => [ParticipatingEntity e] -> Encoding
forall e. ToJSON e => ParticipatingEntity e -> Bool
forall e. ToJSON e => ParticipatingEntity e -> Value
forall e. ToJSON e => ParticipatingEntity e -> Encoding
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: forall e. ToJSON e => ParticipatingEntity e -> Value
toJSON :: ParticipatingEntity e -> Value
$ctoEncoding :: forall e. ToJSON e => ParticipatingEntity e -> Encoding
toEncoding :: ParticipatingEntity e -> Encoding
$ctoJSONList :: forall e. ToJSON e => [ParticipatingEntity e] -> Value
toJSONList :: [ParticipatingEntity e] -> Value
$ctoEncodingList :: forall e. ToJSON e => [ParticipatingEntity e] -> Encoding
toEncodingList :: [ParticipatingEntity e] -> Encoding
$comitField :: forall e. ToJSON e => ParticipatingEntity e -> Bool
omitField :: ParticipatingEntity e -> Bool
ToJSON)
data IntactPlacementLog = IntactPlacementLog
{ IntactPlacementLog -> Bool
isIntact :: Bool
, IntactPlacementLog -> OriginalName
sName :: OriginalName
, IntactPlacementLog -> Cosmic Location
locUpperLeft :: Cosmic Location
}
deriving ((forall x. IntactPlacementLog -> Rep IntactPlacementLog x)
-> (forall x. Rep IntactPlacementLog x -> IntactPlacementLog)
-> Generic IntactPlacementLog
forall x. Rep IntactPlacementLog x -> IntactPlacementLog
forall x. IntactPlacementLog -> Rep IntactPlacementLog x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. IntactPlacementLog -> Rep IntactPlacementLog x
from :: forall x. IntactPlacementLog -> Rep IntactPlacementLog x
$cto :: forall x. Rep IntactPlacementLog x -> IntactPlacementLog
to :: forall x. Rep IntactPlacementLog x -> IntactPlacementLog
Generic, [IntactPlacementLog] -> Value
[IntactPlacementLog] -> Encoding
IntactPlacementLog -> Bool
IntactPlacementLog -> Value
IntactPlacementLog -> Encoding
(IntactPlacementLog -> Value)
-> (IntactPlacementLog -> Encoding)
-> ([IntactPlacementLog] -> Value)
-> ([IntactPlacementLog] -> Encoding)
-> (IntactPlacementLog -> Bool)
-> ToJSON IntactPlacementLog
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: IntactPlacementLog -> Value
toJSON :: IntactPlacementLog -> Value
$ctoEncoding :: IntactPlacementLog -> Encoding
toEncoding :: IntactPlacementLog -> Encoding
$ctoJSONList :: [IntactPlacementLog] -> Value
toJSONList :: [IntactPlacementLog] -> Value
$ctoEncodingList :: [IntactPlacementLog] -> Encoding
toEncodingList :: [IntactPlacementLog] -> Encoding
$comitField :: IntactPlacementLog -> Bool
omitField :: IntactPlacementLog -> Bool
ToJSON)
data SearchLog e
= FoundParticipatingEntity (ParticipatingEntity e)
| StructureRemoved OriginalName
| FoundRowCandidates [FoundRowCandidate e]
| FoundCompleteStructureCandidates [OriginalName]
| IntactStaticPlacement [IntactPlacementLog]
deriving ((forall a b. (a -> b) -> SearchLog a -> SearchLog b)
-> (forall a b. a -> SearchLog b -> SearchLog a)
-> Functor SearchLog
forall a b. a -> SearchLog b -> SearchLog a
forall a b. (a -> b) -> SearchLog a -> SearchLog b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall a b. (a -> b) -> SearchLog a -> SearchLog b
fmap :: forall a b. (a -> b) -> SearchLog a -> SearchLog b
$c<$ :: forall a b. a -> SearchLog b -> SearchLog a
<$ :: forall a b. a -> SearchLog b -> SearchLog a
Functor, (forall x. SearchLog e -> Rep (SearchLog e) x)
-> (forall x. Rep (SearchLog e) x -> SearchLog e)
-> Generic (SearchLog e)
forall x. Rep (SearchLog e) x -> SearchLog e
forall x. SearchLog e -> Rep (SearchLog e) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall e x. Rep (SearchLog e) x -> SearchLog e
forall e x. SearchLog e -> Rep (SearchLog e) x
$cfrom :: forall e x. SearchLog e -> Rep (SearchLog e) x
from :: forall x. SearchLog e -> Rep (SearchLog e) x
$cto :: forall e x. Rep (SearchLog e) x -> SearchLog e
to :: forall x. Rep (SearchLog e) x -> SearchLog e
Generic)
instance (ToJSON e) => ToJSON (SearchLog e) where
toJSON :: SearchLog e -> Value
toJSON = Options -> SearchLog e -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
searchLogOptions
searchLogOptions :: Options
searchLogOptions :: Options
searchLogOptions =
Options
defaultOptions
{ sumEncoding = ObjectWithSingleField
}
instance ToSample (SearchLog e) where
toSamples :: Proxy (SearchLog e) -> [(OriginalName, SearchLog e)]
toSamples Proxy (SearchLog e)
_ = [(OriginalName, SearchLog e)]
forall a. [(OriginalName, a)]
SD.noSamples
data StructureLocation = StructureLocation OriginalName (Cosmic Location)
deriving ((forall x. StructureLocation -> Rep StructureLocation x)
-> (forall x. Rep StructureLocation x -> StructureLocation)
-> Generic StructureLocation
forall x. Rep StructureLocation x -> StructureLocation
forall x. StructureLocation -> Rep StructureLocation x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. StructureLocation -> Rep StructureLocation x
from :: forall x. StructureLocation -> Rep StructureLocation x
$cto :: forall x. Rep StructureLocation x -> StructureLocation
to :: forall x. Rep StructureLocation x -> StructureLocation
Generic, [StructureLocation] -> Value
[StructureLocation] -> Encoding
StructureLocation -> Bool
StructureLocation -> Value
StructureLocation -> Encoding
(StructureLocation -> Value)
-> (StructureLocation -> Encoding)
-> ([StructureLocation] -> Value)
-> ([StructureLocation] -> Encoding)
-> (StructureLocation -> Bool)
-> ToJSON StructureLocation
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: StructureLocation -> Value
toJSON :: StructureLocation -> Value
$ctoEncoding :: StructureLocation -> Encoding
toEncoding :: StructureLocation -> Encoding
$ctoJSONList :: [StructureLocation] -> Value
toJSONList :: [StructureLocation] -> Value
$ctoEncodingList :: [StructureLocation] -> Encoding
toEncodingList :: [StructureLocation] -> Encoding
$comitField :: StructureLocation -> Bool
omitField :: StructureLocation -> Bool
ToJSON)
instance ToSample StructureLocation where
toSamples :: Proxy StructureLocation -> [(OriginalName, StructureLocation)]
toSamples Proxy StructureLocation
_ = [(OriginalName, StructureLocation)]
forall a. [(OriginalName, a)]
SD.noSamples